Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / init01.f90
blob9f75a8d5567330efd4292fd948f1cc4a4e382c8e
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Initializer error tests
4 subroutine objectpointers(j)
5 integer, intent(in) :: j
6 real, allocatable, target, save :: x1
7 real, codimension[*], target, save :: x2
8 real, save :: x3
9 real, target :: x4
10 real, target, save :: x5(10)
11 !ERROR: An initial data target may not be a reference to an ALLOCATABLE 'x1'
12 real, pointer :: p1 => x1
13 !ERROR: An initial data target may not be a reference to a coarray 'x2'
14 real, pointer :: p2 => x2
15 !ERROR: An initial data target may not be a reference to an object 'x3' that lacks the TARGET attribute
16 real, pointer :: p3 => x3
17 !ERROR: An initial data target may not be a reference to an object 'x4' that lacks the SAVE attribute
18 real, pointer :: p4 => x4
19 !ERROR: An initial data target must be a designator with constant subscripts
20 real, pointer :: p5 => x5(j)
21 !ERROR: Pointer has rank 0 but target has rank 1
22 real, pointer :: p6 => x5
24 !TODO: type incompatibility, non-deferred type parameter values, contiguity
26 end subroutine
28 subroutine dataobjects(j)
29 integer, intent(in) :: j
30 real, parameter :: x1(*) = [1., 2.]
31 !ERROR: Implied-shape parameter 'x2' has rank 2 but its initializer has rank 1
32 real, parameter :: x2(*,*) = [1., 2.]
33 !ERROR: Named constant 'x3' array must have constant shape
34 real, parameter :: x3(j) = [1., 2.]
35 !ERROR: Shape of initialized object 'x4' must be constant
36 real :: x4(j) = [1., 2.]
37 !ERROR: Rank of initialized object is 2, but initialization expression has rank 1
38 real :: x5(2,2) = [1., 2., 3., 4.]
39 real :: x6(2,2) = 5.
40 !ERROR: Rank of initialized object is 0, but initialization expression has rank 1
41 real :: x7 = [1.]
42 real :: x8(2,2) = reshape([1., 2., 3., 4.], [2, 2])
43 !ERROR: Dimension 1 of initialized object has extent 3, but initialization expression has extent 2
44 real :: x9(3) = [1., 2.]
45 !ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
46 real :: x10(2,3) = reshape([real::(k,k=1,6)], [3, 2])
47 end subroutine
49 subroutine components(n)
50 integer, intent(in) :: n
51 real, target, save :: a1(3)
52 real, target :: a2
53 real, save :: a3
54 real, target, save :: a4
55 type :: t1
56 !ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
57 real :: x1(2) = [1., 2., 3.]
58 end type
59 type :: t2(kind, len)
60 integer, kind :: kind
61 integer, len :: len
62 !ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
63 !ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
64 real :: x1(2) = [1., 2., 3.]
65 !ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
66 real :: x2(kind) = [1., 2., 3.]
67 !ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
68 !ERROR: Shape of initialized object 'x3' must be constant
69 real :: x3(len) = [1., 2., 3.]
70 real, pointer :: p1(:) => a1
71 !ERROR: An initial data target may not be a reference to an object 'a2' that lacks the SAVE attribute
72 !ERROR: An initial data target may not be a reference to an object 'a2' that lacks the SAVE attribute
73 real, pointer :: p2 => a2
74 !ERROR: An initial data target may not be a reference to an object 'a3' that lacks the TARGET attribute
75 !ERROR: An initial data target may not be a reference to an object 'a3' that lacks the TARGET attribute
76 real, pointer :: p3 => a3
77 !ERROR: Pointer has rank 0 but target has rank 1
78 !ERROR: Pointer has rank 0 but target has rank 1
79 real, pointer :: p4 => a1
80 !ERROR: Pointer has rank 1 but target has rank 0
81 !ERROR: Pointer has rank 1 but target has rank 0
82 real, pointer :: p5(:) => a4
83 end type
84 type(t2(3,2)) :: o1
85 type(t2(2,n)) :: o2
86 type :: t3
87 real :: x
88 end type
89 type(t3), save, target :: o3
90 real, pointer :: p10 => o3%x
91 associate (a1 => o3, a2 => o3%x)
92 block
93 real, pointer :: p11 => a1
94 real, pointer :: p12 => a2
95 end block
96 end associate
97 end subroutine
99 subroutine notObjects
100 !ERROR: 'x1' is not an object that can be initialized
101 real, external :: x1 = 1.
102 !ERROR: 'x2' is not a pointer but is initialized like one
103 real, external :: x2 => sin
104 !ERROR: 'x3' is not an object that can be initialized
105 real, intrinsic :: x3 = 1.
106 !ERROR: 'x4' is not a pointer but is initialized like one
107 real, intrinsic :: x4 => cos
108 end subroutine