aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/pointer_function_actual_2.f90
blob: 11457ffd9a6df392cbc22b9ad38f246ab7d4da0f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
! { dg-do run }
! Tests the fix for PR31200, in which the target x would
! not be associated with p
!
! COntributed by Joost VandeVondele <jv244@cam.ac.uk>
!
  REAL,TARGET :: x
  CALL s3(f(x))
CONTAINS
  FUNCTION f(a)
    REAL,POINTER :: f
    REAL,TARGET :: a
    f => a
  END FUNCTION
  SUBROUTINE s3(targ)
    REAL,TARGET :: targ
    REAL,POINTER :: p
    p => targ
    IF (.NOT. ASSOCIATED(p,x)) CALL ABORT()
  END SUBROUTINE
END