Mercurial > hg > CbC > CbC_gcc
diff gcc/testsuite/gfortran.dg/pointer_function_actual_2.f90 @ 111:04ced10e8804
gcc 7
author | kono |
---|---|
date | Fri, 27 Oct 2017 22:46:09 +0900 |
parents | |
children | 84e7813d76e9 |
line wrap: on
line diff
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/gcc/testsuite/gfortran.dg/pointer_function_actual_2.f90 Fri Oct 27 22:46:09 2017 +0900 @@ -0,0 +1,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 +