nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_2.f03
blob58b0b4ad572af1c027d2f4d8bdf9c4435baf12af
1 ! { dg-do compile }
2 ! { dg-options "-std=f2003" }
4 ! PR 40940: CLASS statement
6 ! Contributed by Janus Weil <janus@gcc.gnu.org>
8 use,intrinsic :: iso_c_binding
10 type t1
11   integer :: comp
12 end type
14 type t2
15   sequence
16   real :: r
17 end type
19 type,bind(c) :: t3
20   integer(c_int) :: i
21 end type
23 type :: t4
24   procedure(absint), pointer :: p  ! { dg-error "Non-polymorphic passed-object dummy argument" }
25 end type
27 type :: t5
28   class(t1) :: c  ! { dg-error "must be allocatable or pointer" }
29 end type
31 abstract interface
32   subroutine absint(arg)
33     import :: t4
34     type(t4) :: arg
35   end subroutine
36 end interface
38 type t6
39   integer :: i
40   class(t6), allocatable :: foo  ! { dg-error "must have the POINTER attribute" }
41 end type t6
44 class(t1) :: o1  ! { dg-error "must be dummy, allocatable or pointer" }
46 class(t2), pointer :: o2  ! { dg-error "is not extensible" }
47 class(t3), pointer :: o3  ! { dg-error "is not extensible" }
49 end