3 ! PR 40176: Fortran 2003: Procedure pointers with array return value
5 ! This example tests for a bug in procedure pointer assignments,
6 ! where the rhs is a dummy.
8 ! Original test case by Barron Bichon <barron.bichon@swri.org>
9 ! Modified by Janus Weil <janus@gcc.gnu.org>
13 PROCEDURE(add
), POINTER :: forig
, fset
17 CALL set_ptr(forig
,fset
)
19 if (forig(1,2) /= fset(1,2)) STOP 1
23 SUBROUTINE set_ptr(f1
,f2
)
24 PROCEDURE(add
), POINTER :: f1
, f2
26 END SUBROUTINE set_ptr