PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / elemental_args_check_3.f90
blob8d63874579477023862e94fae3e3ad6cc0f6d790
1 ! { dg-do compile }
3 ! Check for constraints restricting arguments of ELEMENTAL procedures.
5 ! Contributed by Daniel Kraft, d@domob.eu.
7 PROGRAM main
8 IMPLICIT NONE
10 CONTAINS
12 IMPURE ELEMENTAL SUBROUTINE foobar &
13 (a, & ! { dg-error "must be scalar" }
14 b, & ! { dg-error "POINTER attribute" }
15 c, & ! { dg-error "ALLOCATABLE attribute" }
16 d) ! { dg-error "must have its INTENT specified or have the VALUE attribute" }
17 INTEGER, INTENT(IN) :: a(:)
18 INTEGER, POINTER, INTENT(IN) :: b
19 INTEGER, ALLOCATABLE, INTENT(IN) :: c
20 INTEGER :: d
21 END SUBROUTINE foobar
23 END PROGRAM main