PR rtl-optimization/82913
[official-gcc.git] / gcc / testsuite / gfortran.fortran-torture / compile / pr42781.f90
blob952285063456b846d8090939c5e7946db38aab89
1 ! ICE with gfortran 4.5 at -O1:
2 !gfcbug98.f90: In function ‘convert_cof’:
3 !gfcbug98.f90:36:0: internal compiler error: in pt_solutions_same_restrict_base,
4 !at tree-ssa-structalias.c:5072
5 module foo
6 implicit none
7 type t_time
8 integer :: secs = 0
9 end type t_time
10 contains
11 elemental function time_cyyyymmddhh (cyyyymmddhh) result (time)
12 type (t_time) :: time
13 character(len=10),intent(in) :: cyyyymmddhh
14 end function time_cyyyymmddhh
16 function nf90_open(path, mode, ncid)
17 character(len = *), intent(in) :: path
18 integer, intent(in) :: mode
19 integer, intent(out) :: ncid
20 integer :: nf90_open
21 end function nf90_open
22 end module foo
23 !==============================================================================
24 module gfcbug98
25 use foo
26 implicit none
28 type t_fileinfo
29 character(len=10) :: atime = ' '
30 end type t_fileinfo
32 type t_body
33 real :: bg(10)
34 end type t_body
35 contains
36 subroutine convert_cof (ifile)
37 character(len=*) ,intent(in) :: ifile
39 character(len=5) :: version
40 type(t_fileinfo) :: gattr
41 type(t_time) :: atime
42 type(t_body),allocatable :: tmp_dat(:)
43 real ,allocatable :: BDA(:, :, :)
45 call open_input
46 call convert_data
47 contains
48 subroutine open_input
49 integer :: i,j
50 version = ''
51 j = nf90_open(ifile, 1, i)
52 end subroutine open_input
53 !--------------------------------------------------------------------------
54 subroutine convert_data
55 BDA(1,:,1) = tmp_dat(1)% bg(:)
56 atime = time_cyyyymmddhh (gattr% atime)
57 end subroutine convert_data
58 end subroutine convert_cof
59 end module gfcbug98