OSDN Git Service

PR c++/9335
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / abstract_type_4.f03
1 ! { dg-do "compile" }
2
3 ! Abstract Types.
4 ! Check for module file IO.
5
6 MODULE m
7   IMPLICIT NONE
8
9   TYPE, ABSTRACT :: abst_t
10     INTEGER :: x
11   END TYPE abst_t
12
13   TYPE, EXTENDS(abst_t) :: concrete_t
14     INTEGER :: y
15   END TYPE concrete_t
16
17 END MODULE m
18
19 PROGRAM main
20   USE m
21   IMPLICIT NONE
22
23   TYPE(abst_t) :: abst ! { dg-error "is of the ABSTRACT type 'abst_t'" }
24   TYPE(concrete_t) :: conc
25
26   ! See if constructing the extending type works.
27   conc = concrete_t (1, 2)
28 END PROGRAM main
29 ! { dg-final { cleanup-modules "m" } }