* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / char_result_15.f90
blob3c9a879d359a6ca676d95719266774924e51589c
1 ! { dg-do run }
3 ! Tests the fix for PR44265. This test arose because of an issue found
4 ! during the development of the fix; namely the clash between the normal
5 ! module parameter and that found in the specification expression for
6 ! 'Get'.
8 ! Contributed by Paul Thomas <pault@gcc.gnu.org>
10 MODULE Fruits
11 IMPLICIT NONE
12 PRIVATE
13 character (20) :: buffer
14 PUBLIC :: Get, names, fruity, buffer
15 CHARACTER(len=7), PARAMETER :: names(3) = [ &
16 'Pomme ', &
17 'Orange ', &
18 'Mangue ' ];
19 CONTAINS
20 FUNCTION Get(i) RESULT(s)
21 CHARACTER(len=7), PARAMETER :: names(3) = [ &
22 'Apple ', &
23 'Orange ', &
24 'Mango ' ];
25 INTEGER, INTENT(IN) :: i
26 CHARACTER(LEN_TRIM(names(i))) :: s
27 s = names(i)
28 END FUNCTION Get
29 subroutine fruity (i)
30 integer :: i
31 write (buffer, '(i2,a)') len (Get (i)), Get (i)
32 end subroutine
33 END MODULE Fruits
35 PROGRAM WheresThatbLinkingConstantGone
36 USE Fruits
37 IMPLICIT NONE
38 integer :: i
39 write (buffer, '(i2,a)') len (Get (1)), Get (1)
40 if (trim (buffer) .ne. " 5Apple") call abort
41 call fruity(3)
42 if (trim (buffer) .ne. " 5Mango") call abort
43 if (trim (names(3)) .ne. "Mangue") Call abort
44 END PROGRAM WheresThatbLinkingConstantGone