Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / allocate03.f90
blobf7cad583b2cec144d65b7f9d2e359fa3dbd7195b
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Check for semantic errors in ALLOCATE statements
4 subroutine C933_a(b1, ca3, ca4, cp3, cp3mold, cp4, cp7, cp8, bsrc)
5 ! If any allocate-object has a deferred type parameter, is unlimited polymorphic,
6 ! or is of abstract type, either type-spec or source-expr shall appear.
8 ! Only testing deferred type parameters here.
10 type SomeType(k, l1, l2)
11 integer, kind :: k = 1
12 integer, len :: l1
13 integer, len :: l2 = 3
14 character(len=l2+l1) str
15 end type
17 type B(l)
18 integer, len :: l
19 character(:), allocatable :: msg
20 type(SomeType(4, l, :)), pointer :: something
21 end type
23 character(len=:), allocatable :: ca1, ca2(:)
24 character(len=*), allocatable :: ca3, ca4(:)
25 character(len=2), allocatable :: ca5, ca6(:)
26 character(len=5) mold
28 type(SomeType(l1=:,l2=:)), pointer :: cp1, cp2(:)
29 type(SomeType(l1=3,l2=4)) cp1mold
30 type(SomeType(1,*,:)), pointer :: cp3, cp4(:)
31 type(SomeType(1,*,5)) cp3mold
32 type(SomeType(l1=:)), pointer :: cp5, cp6(:)
33 type(SomeType(l1=6)) cp5mold
34 type(SomeType(1,*,*)), pointer :: cp7, cp8(:)
35 type(SomeType(1, l1=3)), pointer :: cp9, cp10(:)
37 type(B(*)) b1
38 type(B(:)), allocatable :: b2
39 type(B(5)) b3
41 type(SomeType(4, *, 8)) bsrc
43 ! Expecting errors: need type-spec/src-expr
44 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
45 allocate(ca1)
46 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
47 allocate(ca2(4))
48 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
49 allocate(cp1)
50 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
51 allocate(cp2(2))
52 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
53 allocate(cp3)
54 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
55 allocate(cp4(2))
56 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
57 allocate(cp5)
58 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
59 allocate(cp6(2))
60 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
61 allocate(b1%msg)
62 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
63 allocate(b1%something)
64 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
65 allocate(b2%msg)
66 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
67 allocate(b2%something)
68 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
69 allocate(b3%msg)
70 !ERROR: Either type-spec or source-expr must appear in ALLOCATE when allocatable object has a deferred type parameters
71 allocate(b3%something)
73 ! Nominal cases, expecting no errors
74 allocate(character(len=5):: ca2(4))
75 allocate(character(len=5):: ca1)
76 allocate(character*5:: ca1)
77 allocate(ca2(4), MOLD = "abcde")
78 allocate(ca2(2), MOLD = (/"abcde", "fghij"/))
79 allocate(ca1, MOLD = mold)
80 allocate(ca2(4), SOURCE = "abcde")
81 allocate(ca2(2), SOURCE = (/"abcde", "fghij"/))
82 allocate(ca1, SOURCE = mold)
83 allocate(SomeType(l1=1, l2=2):: cp1, cp2(2))
84 allocate(SomeType(1,*,5):: cp3, cp4(2)) !OK, but segfaults gfortran
85 allocate(SomeType(l1=1):: cp5, cp6(2))
86 allocate(cp1, cp2(2), mold = cp1mold)
87 allocate(cp3, cp4(2), mold = cp3mold)
88 allocate(cp5, cp6(2), mold = cp5mold)
89 allocate(cp1, cp2(2), source = cp1mold)
90 allocate(cp3, cp4(2), source = cp3mold)
91 allocate(cp5, cp6(2), source = cp5mold)
92 allocate(character(len=10):: b1%msg, b2%msg, b3%msg)
93 allocate(SomeType(4, b1%l, 9):: b1%something)
94 allocate(b2%something, source=bsrc)
95 allocate(SomeType(4, 5, 8):: b3%something)
97 ! assumed/explicit length do not need type-spec/mold
98 allocate(ca3, ca4(4))
99 allocate(ca5, ca6(4))
100 allocate(cp7, cp8(2))
101 allocate(cp9, cp10(2))
103 end subroutine