aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / generic_32.f90
blob61e8a2ab123508b7f47e0ca5553412c5814ec603
1 ! { dg-do compile }
3 ! PR 45521: [F08] GENERIC resolution with ALLOCATABLE/POINTER and PROCEDURE
5 ! Contributed by Janus Weil <janus@gcc.gnu.org>
8 INTERFACE gen
9 SUBROUTINE suba(a) ! { dg-error "Ambiguous interfaces" }
10 REAL,ALLOCATABLE :: a(:)
11 END SUBROUTINE
12 SUBROUTINE subp(p) ! { dg-error "Ambiguous interfaces" }
13 REAL,POINTER,INTENT(IN) :: p(:)
14 END SUBROUTINE
15 END INTERFACE
16 end