1289715Sglebius! { dg-do compile }
2289715Sglebius! { dg-options "-std=legacy" }
3289715Sglebius! We want to check for statement functions, thus legacy mode.
4289715Sglebius
5289715Sglebius! Check for errors with declarations not allowed within BLOCK.
6289715Sglebius
7289715SglebiusSUBROUTINE proc (a)
8289715Sglebius  IMPLICIT NONE
9289715Sglebius  INTEGER :: a
10289715Sglebius
11289715Sglebius  BLOCK
12289715Sglebius    INTENT(IN) :: a ! { dg-error "not allowed inside of BLOCK" }
13289715Sglebius    VALUE :: a ! { dg-error "not allowed inside of BLOCK" }
14289715Sglebius    OPTIONAL :: a ! { dg-error "not allowed inside of BLOCK" }
15289715Sglebius  END BLOCK
16289715SglebiusEND SUBROUTINE proc
17289715Sglebius
18289715SglebiusPROGRAM main
19289715Sglebius  IMPLICIT NONE
20289715Sglebius
21289715Sglebius  BLOCK 
22289715Sglebius    IMPLICIT INTEGER(a-z) ! { dg-error "not allowed inside of BLOCK" }
23289715Sglebius    INTEGER :: a, b, c, d
24289715Sglebius    INTEGER :: stfunc
25289715Sglebius    stfunc(a, b) = a + b ! { dg-error "not allowed inside of BLOCK" }
26289715Sglebius    EQUIVALENCE (a, b) ! { dg-error "not allowed inside of BLOCK" }
27289715Sglebius    NAMELIST /NLIST/ a, b ! { dg-error "not allowed inside of BLOCK" }
28289715Sglebius    COMMON /CBLOCK/ c, d ! { dg-error "not allowed inside of BLOCK" }
29289715Sglebius  ! This contains is in the specification part.
30289715Sglebius  CONTAINS ! { dg-error "Unexpected CONTAINS statement" }
31289715Sglebius  END BLOCK
32289715Sglebius
33289715Sglebius  BLOCK
34    PRINT *, "Hello, world"
35  ! This one in the executable statement part.
36  CONTAINS ! { dg-error "Unexpected CONTAINS statement" }
37  END BLOCK
38END PROGRAM main
39