Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / allocate01.f90
bloba66e2467cbe4e68b2d3cff40d5af74dd9a78111d
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Check for semantic errors in ALLOCATE statements
4 ! Creating a symbol that allocate should accept
5 module share
6 real, pointer :: rp
7 end module share
9 module m
10 ! Creating symbols that allocate should not accept
11 type :: a_type
12 real, allocatable :: x
13 contains
14 procedure, pass :: foo => mfoo
15 procedure, pass :: bar => mbar
16 end type
18 contains
19 function mfoo(x)
20 class(a_type) :: x
21 class(a_type), allocatable :: foo
22 foo = x
23 end function
24 subroutine mbar(x)
25 class(a_type) :: x
26 end subroutine
27 end module
29 subroutine C932(ed1, ed5, ed7, edc9, edc10, okad1, okpd1, okacd5)
30 ! Each allocate-object shall be a data pointer or an allocatable variable.
31 use :: share
32 use :: m, only: a_type
33 type TestType1
34 integer, allocatable :: ok(:)
35 integer :: nok(10)
36 end type
37 type TestType2
38 integer, pointer :: ok
39 integer :: nok
40 end type
41 interface
42 function foo(x)
43 real(4) :: foo, x
44 end function
45 subroutine bar()
46 end subroutine
47 end interface
48 real ed1(:), e2
49 real, save :: e3[*]
50 real , target :: e4, ed5(:)
51 real , parameter :: e6 = 5.
52 procedure(foo), pointer :: proc_ptr1 => NULL()
53 procedure(bar), pointer :: proc_ptr2
54 type(TestType1) ed7
55 type(TestType2) e8
56 type(TestType1) edc9[*]
57 type(TestType2) edc10[*]
58 class(a_type), allocatable :: a_var
60 real, allocatable :: oka1(:, :), okad1(:, :), oka2
61 real, pointer :: okp1(:, :), okpd1(:, :), okp2
62 real, pointer, save :: okp3
63 real, allocatable, save :: oka3, okac4[:,:]
64 real, allocatable :: okacd5(:, :)[:]
66 !ERROR: Name in ALLOCATE statement must be a variable name
67 allocate(foo)
68 !ERROR: Name in ALLOCATE statement must be a variable name
69 allocate(bar)
70 !ERROR: Name in ALLOCATE statement must be a variable name
71 allocate(C932)
72 !ERROR: Name in ALLOCATE statement must be a variable name
73 allocate(proc_ptr1)
74 !ERROR: Name in ALLOCATE statement must be a variable name
75 allocate(proc_ptr2)
76 !ERROR: Name in ALLOCATE statement must be a variable name
77 allocate(a_var%foo)
78 !ERROR: Name in ALLOCATE statement must be a variable name
79 allocate(a_var%bar)
81 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
82 allocate(ed1)
83 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
84 allocate(e2)
85 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
86 allocate(e3)
87 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
88 allocate(e4)
89 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
90 allocate(ed5)
91 !ERROR: Name in ALLOCATE statement must be a variable name
92 allocate(e6)
93 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
94 allocate(ed7)
95 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
96 allocate(ed7%nok(2))
97 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
98 allocate(ed8)
99 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
100 allocate(ed8)
101 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
102 allocate(edc9%nok)
103 !ERROR: Entity in ALLOCATE statement must have the ALLOCATABLE or POINTER attribute
104 allocate(edc10)
106 ! No errors expected below:
107 allocate(a_var)
108 allocate(a_var%x)
109 allocate(oka1(5, 7), okad1(4, 8), oka2)
110 allocate(okp1(5, 7), okpd1(4, 8), okp2)
111 allocate(okp1(5, 7), okpd1(4, 8), okp2)
112 allocate(okp3, oka3)
113 allocate(okac4[2:4,4:*])
114 allocate(okacd5(1:2,3:4)[5:*])
115 allocate(ed7%ok(7))
116 allocate(e8%ok)
117 allocate(edc9%ok(4))
118 allocate(edc10%ok)
119 allocate(rp)
120 end subroutine