OSDN Git Service

PR debug/43329
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / module_read_2.f90
1 ! { dg-do run }
2 !
3 ! PR fortran/43199
4 !
5 ! This program gave an ICE due to reading the REF_COMPONENT with CLASS.
6 !
7 module m_string
8   type t_string
9       character, dimension(:), allocatable :: string
10   end type t_string
11 contains
12 pure function string_to_char ( s ) result(res)
13   class(t_string), intent(in) :: s
14   character(len=size(s%string)) :: res
15   integer :: i
16   do i = 1,len(res)
17     res(i:i) = s%string(i)
18   end do
19 end function string_to_char
20 end module m_string
21
22 use m_string
23 type(t_string) :: str
24 allocate(str%string(5))
25 str%string = ['H','e','l','l','o']
26 if (len (string_to_char (str)) /= 5) call abort ()
27 if (string_to_char (str) /= "Hello") call abort ()
28 end
29
30 ! { dg-final { cleanup-modules "m_string" } }