[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / access_spec_2.f90
blobccb56e2cdc23481cb7b6185d420dffde22e81ea0
1 ! { dg-do compile }
2 ! { dg-options "-std=f95" }
3 ! PR fortran/31472
4 ! Access specifications: Invalid Fortran 95 code
6 module test
7 implicit none
8 integer, public :: x
9 public :: x ! { dg-error "was already specified" }
10 private :: x ! { dg-error "was already specified" }
11 end module test
13 module mod
14 implicit none
15 private
16 type, public :: bar
17 PRIVATE
18 integer, public :: y ! { dg-error "Fortran 2003: Attribute PUBLIC" }
19 integer, public :: z ! { dg-error "Fortran 2003: Attribute PUBLIC" }
20 end type ! { dg-error "Derived type definition at" }
21 contains
22 subroutine foo
23 integer :: x
24 private :: x ! { dg-error "only allowed in the specification part of a module" }
25 type, private :: t ! { dg-error "only be PRIVATE in the specification part of a module" }
26 integer :: z
27 end type t ! { dg-error "Expecting END SUBROUTINE statement" }
28 type :: ttt
29 integer,public :: z ! { dg-error "not allowed outside of the specification part of a module" }
30 end type ttt ! { dg-error "Derived type definition at" }
31 end subroutine
32 end module
34 program x
35 implicit none
36 integer :: i
37 public :: i ! { dg-error "only allowed in the specification part of a module" }
38 integer,public :: j ! { dg-error "not allowed outside of the specification part of a module" }
39 end program x