OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc2/] [gcc/] [testsuite/] [gfortran.fortran-torture/] [compile/] [pr42781.f90] - Diff between revs 303 and 384

Go to most recent revision | Only display areas with differences | Details | Blame | View Log

Rev 303 Rev 384
! ICE with gfortran 4.5 at -O1:
! ICE with gfortran 4.5 at -O1:
!gfcbug98.f90: In function ‘convert_cof’:
!gfcbug98.f90: In function ‘convert_cof’:
!gfcbug98.f90:36:0: internal compiler error: in pt_solutions_same_restrict_base,
!gfcbug98.f90:36:0: internal compiler error: in pt_solutions_same_restrict_base,
!at tree-ssa-structalias.c:5072
!at tree-ssa-structalias.c:5072
module foo
module foo
  implicit none
  implicit none
  type t_time
  type t_time
     integer :: secs = 0
     integer :: secs = 0
  end type t_time
  end type t_time
contains
contains
  elemental function time_cyyyymmddhh (cyyyymmddhh) result (time)
  elemental function time_cyyyymmddhh (cyyyymmddhh) result (time)
    type (t_time)                :: time
    type (t_time)                :: time
    character(len=10),intent(in) :: cyyyymmddhh
    character(len=10),intent(in) :: cyyyymmddhh
  end function time_cyyyymmddhh
  end function time_cyyyymmddhh
  function nf90_open(path, mode, ncid)
  function nf90_open(path, mode, ncid)
    character(len = *), intent(in) :: path
    character(len = *), intent(in) :: path
    integer, intent(in)  :: mode
    integer, intent(in)  :: mode
    integer, intent(out) :: ncid
    integer, intent(out) :: ncid
    integer              :: nf90_open
    integer              :: nf90_open
  end function nf90_open
  end function nf90_open
end module foo
end module foo
!==============================================================================
!==============================================================================
module gfcbug98
module gfcbug98
  use foo
  use foo
  implicit none
  implicit none
  type t_fileinfo
  type t_fileinfo
     character(len=10) :: atime = ' '
     character(len=10) :: atime = ' '
  end type t_fileinfo
  end type t_fileinfo
  type t_body
  type t_body
     real         :: bg(10)
     real         :: bg(10)
  end type t_body
  end type t_body
contains
contains
  subroutine convert_cof (ifile)
  subroutine convert_cof (ifile)
    character(len=*) ,intent(in) :: ifile
    character(len=*) ,intent(in) :: ifile
    character(len=5)         :: version
    character(len=5)         :: version
    type(t_fileinfo)         :: gattr
    type(t_fileinfo)         :: gattr
    type(t_time)             :: atime
    type(t_time)             :: atime
    type(t_body),allocatable :: tmp_dat(:)
    type(t_body),allocatable :: tmp_dat(:)
    real        ,allocatable :: BDA(:, :, :)
    real        ,allocatable :: BDA(:, :, :)
    call open_input
    call open_input
    call convert_data
    call convert_data
  contains
  contains
    subroutine open_input
    subroutine open_input
      integer             :: i,j
      integer             :: i,j
      version = ''
      version = ''
      j = nf90_open(ifile, 1, i)
      j = nf90_open(ifile, 1, i)
    end subroutine open_input
    end subroutine open_input
    !--------------------------------------------------------------------------
    !--------------------------------------------------------------------------
    subroutine convert_data
    subroutine convert_data
      BDA(1,:,1) = tmp_dat(1)% bg(:)
      BDA(1,:,1) = tmp_dat(1)% bg(:)
      atime = time_cyyyymmddhh (gattr% atime)
      atime = time_cyyyymmddhh (gattr% atime)
    end subroutine convert_data
    end subroutine convert_data
  end subroutine convert_cof
  end subroutine convert_cof
end module gfcbug98
end module gfcbug98
 
 

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.