xref: /llvm-project/flang/test/Semantics/resolve31.f90 (revision 79910786324eca8d5a0535f6361b507c3d38f61f)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2! C735 If EXTENDS appears, SEQUENCE shall not appear.
3! C738 The same private-or-sequence shall not appear more than once in a
4! given derived-type-def .
5!
6! C740 If SEQUENCE appears,
7!  the type shall have at least one component,
8!  each data component shall be declared to be of an intrinsic type or of a sequence type,
9!  the derived type shall not have any type parameter,
10!  and a type-bound-procedure-part shall not appear.
11subroutine s1
12  integer :: t0
13  !ERROR: 't0' is not a derived type
14  type(t0) :: x
15  type :: t1
16  end type
17  type, extends(t1) :: t2
18  end type
19  !ERROR: Derived type 't3' not found
20  type, extends(t3) :: t4
21  end type
22  !ERROR: 't0' is not a derived type
23  type, extends(t0) :: t5
24  end type
25end subroutine
26
27module m1
28  type t0
29  end type
30end
31module m2
32  type t
33  end type
34end
35module m3
36  type t0
37  end type
38end
39subroutine s2
40  use m1
41  use m2, t0 => t
42  use m3
43  !ERROR: Reference to 't0' is ambiguous
44  type, extends(t0) :: t1
45  end type
46end subroutine
47
48module m4
49  type :: t1
50    private
51    sequence
52    !WARNING: PRIVATE should not appear more than once in derived type components
53    private
54    !WARNING: SEQUENCE should not appear more than once in derived type components
55    sequence
56    real :: t1Field
57  end type
58  type :: t1a
59  end type
60  !ERROR: A sequence type may not have the EXTENDS attribute
61  type, extends(t1a) :: t2
62    sequence
63    integer i
64  end type
65  type :: t3
66    sequence
67    integer i
68  !ERROR: A sequence type may not have a CONTAINS statement
69  contains
70  end type
71  !WARNING: A sequence type should have at least one component
72  type :: emptyType
73    sequence
74  end type emptyType
75  type :: plainType
76    real :: plainField
77  end type plainType
78  type :: sequenceType
79    sequence
80    real :: sequenceField
81  end type sequenceType
82  type :: testType
83    sequence
84    !ERROR: A sequence type data component must either be of an intrinsic type or a derived sequence type
85    class(*), allocatable :: typeStarField
86    !ERROR: A sequence type data component must either be of an intrinsic type or a derived sequence type
87    type(plainType) :: testField1
88    !WARNING: A sequence type data component that is a pointer to a non-sequence type is not standard
89    type(plainType), pointer :: testField1p
90    type(sequenceType) :: testField2
91    procedure(real), pointer, nopass :: procField
92  end type testType
93  !ERROR: A sequence type may not have type parameters
94  type :: paramType(param)
95    integer, kind :: param
96    sequence
97    real :: paramField
98  end type paramType
99contains
100  subroutine s3
101    type :: t1
102      !ERROR: PRIVATE is only allowed in a derived type that is in a module
103      private
104    contains
105      !ERROR: PRIVATE is only allowed in a derived type that is in a module
106      private
107    end type
108  end
109end
110