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

PROGRAM WheresThatbLinkingConstantGone
  USE Fruits
  IMPLICIT NONE
  integer :: i
  write (buffer, '(i2,a)') len (Get (1)), Get (1)
  if (trim (buffer) .ne. " 5Apple") STOP 1
  call fruity(3)
  if (trim (buffer) .ne. " 5Mango") STOP 2
  if (trim (names(3)) .ne. "Mangue") STOP 3
END PROGRAM WheresThatbLinkingConstantGone