AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_ptr_comp_19.f90
blobb9b7da25e9dbecc0eac9c7b7fb06c5f2ce36ebc3
1 ! { dg-do run }
3 ! PR 41139: [4.5 Regression] a procedure pointer call as actual argument
5 ! Contributed by Janus Weil <janus@gcc.gnu.org>
7 PROGRAM test
9 type :: t
10 PROCEDURE(three), POINTER, nopass :: f
11 end type
12 type(t) :: o
13 logical :: g
15 o%f => three
16 g=greater(4.,o%f())
17 if (.not. g) STOP 1
19 CONTAINS
21 REAL FUNCTION three()
22 three = 3.
23 END FUNCTION
25 LOGICAL FUNCTION greater(x,y)
26 REAL, INTENT(in) :: x, y
27 print *,"greater:",x,y
28 greater = (x > y)
29 END FUNCTION greater
31 END PROGRAM test