xref: /llvm-project/flang/test/Semantics/resolve70.f90 (revision 6c1ac141d3c98af9738bc77fcb55602cbff7751f)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! C703 (R702) The derived-type-spec shall not specify an abstract type (7.5.7).
3! This constraint refers to the derived-type-spec in a type-spec.  A type-spec
4! can appear in an ALLOCATE statement, an ac-spec for an array constructor, and
5! in the type specifier of a TYPE GUARD statement
6!
7! C706 TYPE(derived-type-spec) shall not specify an abstract type (7.5.7).
8!   This is for a declaration-type-spec
9!
10! C796 (R756) The derived-type-spec shall not specify an abstract type (7.5.7).
11!
12! C705 (R703) In a declaration-type-spec that uses the CLASS keyword,
13! derived-type-spec shall specify an extensible type (7.5.7).
14subroutine s()
15  type, abstract :: abstractType
16  end type abstractType
17
18  type, extends(abstractType) :: concreteType
19  end type concreteType
20
21  ! declaration-type-spec
22  !ERROR: ABSTRACT derived type may not be used here
23  type (abstractType), allocatable :: abstractVar
24
25  ! ac-spec for an array constructor
26  !ERROR: ABSTRACT derived type may not be used here
27  type (abstractType), parameter :: abstractArray(*) = (/ abstractType :: /)
28
29  class(*), allocatable :: selector
30
31  ! Structure constructor
32  !ERROR: ABSTRACT derived type may not be used here
33  !ERROR: ABSTRACT derived type 'abstracttype' may not be used in a structure constructor
34  type (abstractType) :: abstractVar1 = abstractType()
35
36  ! Allocate statement
37  !ERROR: ABSTRACT derived type may not be used here
38  allocate(abstractType :: abstractVar)
39
40  select type(selector)
41    ! Type specifier for a type guard statement
42    !ERROR: ABSTRACT derived type may not be used here
43    type is (abstractType)
44  end select
45end subroutine s
46
47subroutine s1()
48  type :: extensible
49  end type
50  type, bind(c) :: inextensible
51  end type
52
53  ! This one's OK
54  class(extensible), allocatable :: y
55
56  !ERROR: Non-extensible derived type 'inextensible' may not be used with CLASS keyword
57  class(inextensible), allocatable :: x
58end subroutine s1
59
60subroutine s2()
61  type t
62    integer i
63  end type t
64  type, extends(t) :: t2
65    real x
66  end type t2
67contains
68  function f1(dummy)
69    class(*) dummy
70    type(t) f1(1)
71    !ERROR: Cannot have an unlimited polymorphic value in an array constructor
72    f1 = [ (dummy) ]
73  end function f1
74end subroutine s2
75