1! RUN: %S/test_errors.sh %s %t %f18
2! Check for semantic errors in ALLOCATE statements
3
4
5subroutine C933_b(n)
6! If any allocate-object has a deferred type parameter, is unlimited polymorphic,
7! or is of abstract type, either type-spec or source-expr shall appear.
8
9! only testing unlimited polymorphic and abstract-type here
10
11  type, abstract :: Base
12    integer x
13  end type
14
15  type, extends(Base) :: A
16    integer y
17  end type
18
19  type, extends(Base) :: B
20    class(Base), allocatable :: y
21  end type
22
23  type C
24    class(*), pointer :: whatever
25    real, pointer :: y
26  end type
27
28  integer n
29  class(*), allocatable :: u1, u2(:)
30  class(C), allocatable :: n1, n2(:)
31  class(Base), pointer :: p1, p2(:)
32  class(B), pointer :: p3, p4(:)
33  type(A) :: molda = A(1, 2)
34
35  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is unlimited polymorphic
36  allocate(u1)
37  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is unlimited polymorphic
38  allocate(u2(2))
39  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is unlimited polymorphic
40  allocate(n1%whatever)
41  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is unlimited polymorphic
42  allocate(n2(2)%whatever)
43  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is of abstract type
44  allocate(p1)
45  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is of abstract type
46  allocate(p2(2))
47  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is of abstract type
48  allocate(p3%y)
49  !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object is of abstract type
50  allocate(p4(2)%y)
51  !WRONG allocate(Base:: u1)
52
53  ! No error expected
54  allocate(real:: u1, u2(2))
55  allocate(A:: u1, u2(2))
56  allocate(C:: u1, u2(2))
57  allocate(character(n):: u1, u2(2))
58  allocate(C:: n1%whatever, n2(2)%whatever)
59  allocate(A:: p1, p2(2))
60  allocate(B:: p3%y, p4(2)%y)
61  allocate(u1, u2(2), MOLD = cos(5.+n))
62  allocate(u1, u2(2), MOLD = molda)
63  allocate(u1, u2(2), MOLD = n1)
64  allocate(u1, u2(2), MOLD = new_line("a"))
65  allocate(n1%whatever, MOLD = n2(1))
66  allocate(p1, p2(2), MOLD = p3)
67  allocate(p3%y, p4(2)%y, MOLD = B(5))
68  allocate(u1, u2(2), SOURCE = cos(5.+n))
69  allocate(u1, u2(2), SOURCE = molda)
70  allocate(u1, u2(2), SOURCE = n1)
71  allocate(u1, u2(2), SOURCE = new_line("a"))
72  allocate(n1%whatever, SOURCE = n2(1))
73  allocate(p1, p2(2), SOURCE = p3)
74  allocate(p3%y, p4(2)%y, SOURCE = B(5))
75
76  ! OK, not unlimited polymorphic or abstract
77  allocate(n1, n2(2))
78  allocate(p3, p4(2))
79end subroutine
80