aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_ptr_comp_2.f90
blob84e98a693f7167f29884ef7412778d7e59cd55c4
1 ! { dg-do run }
3 ! PR39630: Fortran 2003: Procedure pointer components.
5 ! Basic test for PPCs with FUNCTION interface and NOPASS.
7 ! Contributed by Janus Weil <janus@gcc.gnu.org>
9 type t
10 procedure(fcn), pointer, nopass :: ppc
11 procedure(abstr), pointer, nopass :: ppc1
12 integer :: i
13 end type
15 abstract interface
16 integer function abstr(x)
17 integer, intent(in) :: x
18 end function
19 end interface
21 type(t) :: obj
22 procedure(fcn), pointer :: f
23 integer :: base
25 intrinsic :: iabs
27 ! Check with interface from contained function
28 obj%ppc => fcn
29 base=obj%ppc(2)
30 if (base/=4) STOP 1
31 call foo (obj%ppc,3)
33 ! Check with abstract interface
34 obj%ppc1 => obj%ppc
35 base=obj%ppc1(4)
36 if (base/=8) STOP 1
37 call foo (obj%ppc1,5)
39 ! Check compatibility components with non-components
40 f => obj%ppc
41 base=f(6)
42 if (base/=12) STOP 1
43 call foo (f,7)
45 contains
47 integer function fcn(x)
48 integer, intent(in) :: x
49 fcn = 2 * x
50 end function
52 subroutine foo (arg, i)
53 procedure (fcn), pointer :: arg
54 integer :: i
55 if (arg(i)/=2*i) STOP 1
56 end subroutine
58 end