RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / pure_formal_proc_2.f90
blobc683a6c51f9bfe7294aa25d71a115151cdcc1c68
1 ! { dg-do compile }
2 ! Tests the fix for PR36526, in which the call to getStrLen would
3 ! generate an error due to the use of a wrong symbol in interface.c
5 ! Contributed by Bálint Aradi <aradi@bccms.uni-bremen.de>
7 module TestPure
8 implicit none
10 type T1
11 character(10) :: str
12 end type T1
14 contains
16 pure function getT1Len(self) result(t1len)
17 type(T1), pointer :: self
18 integer :: t1len
20 t1len = getStrLen(self%str)
22 end function getT1Len
25 pure function getStrLen(str) result(length)
26 character(*), intent(in) :: str
27 integer :: length
29 length = len_trim(str)
31 end function getStrLen
33 end module TestPure
36 program Test
37 use TestPure
38 implicit none
40 type(T1), pointer :: pT1
42 allocate(pT1)
43 pT1%str = "test"
44 write (*,*) getT1Len(pT1)
45 deallocate(pT1)
47 end program Test