Daily bump.
[official-gcc.git] / gcc / testsuite / gfortran.dg / arrayio_11.f90
blob39255dbcdaef4143ecd29c25bf1dd2d2db031803
1 ! { dg-do run }
2 ! Tests the fix for PR30284, in which the substring plus
3 ! component reference for an internal file would cause an ICE.
5 ! Contributed by Harald Anlauf <anlauf@gmx.de>
7 program gfcbug51
8 implicit none
10 type :: date_t
11 character(len=12) :: date ! yyyymmddhhmm
12 end type date_t
14 type year_t
15 integer :: year = 0
16 end type year_t
18 type(date_t) :: file(3)
19 type(year_t) :: time(3)
21 FILE%date = (/'200612231200', '200712231200', &
22 '200812231200'/)
24 time = date_to_year (FILE)
25 if (any (time%year .ne. (/2006, 2007, 2008/))) call abort ()
27 call month_to_date ((/8, 9, 10/), FILE)
28 if ( any (file%date .ne. (/'200608231200', '200709231200', &
29 '200810231200'/))) call abort ()
31 contains
33 function date_to_year (d) result (y)
34 type(date_t) :: d(3)
35 type(year_t) :: y(size (d, 1))
36 read (d%date(1:4),'(i4)') time% year
37 end function date_to_year
39 subroutine month_to_date (m, d)
40 type(date_t) :: d(3)
41 integer :: m(:)
42 write (d%date(5:6),'(i2.2)') m
43 end subroutine month_to_date
45 end program gfcbug51