2013-10-29 Tobias Burnus <burnus@net-b.de>
[official-gcc.git] / gcc / testsuite / gfortran.dg / blockdata_8.f90
blobd3f992564ad7ade2b4b984f5f9c8926938019148
1 ! { dg-do compile }
3 ! PR fortran/44350
5 ! Fortran 2008, C1116 only permits a small subset of statements in BLOCK DATA
7 ! Part of the test case was contributed by Vittorio Zecca
9 module m
10 end module m
12 BLOCK DATA valid2
13 use m
14 implicit integer(a-z)
15 intrinsic :: sin
16 common /one/ a, c
17 bind(C) :: /one/
18 dimension c(5)
19 parameter (g = 7)
20 END BLOCK DATA valid2
22 BLOCK DATA valid
23 use m
24 implicit none
25 type t
26 sequence
27 end type t
28 type(t), save :: x
29 integer :: y
30 real :: q
31 save :: y
32 dimension :: q(5)
33 ! class(*) :: zz ! See PR fortran/58857
34 ! pointer :: zz
35 target :: q
36 volatile y
37 asynchronous q
38 END BLOCK DATA valid
40 block data invalid
41 common x
42 f(x)=x ! { dg-error "STATEMENT FUNCTION statement is not allowed inside of BLOCK DATA" }
43 interface ! { dg-error "INTERFACE statement is not allowed inside of BLOCK DATA" }
44 end interface
45 1 format() ! { dg-error "FORMAT statement is not allowed inside of BLOCK DATA" }
46 end block invalid ! { dg-error "Expecting END BLOCK DATA statement" }
48 ! { dg-error "Unexpected end of file" "" { target "*-*-*" } 0 }