xref: /llvm-project/flang/test/Semantics/data01.f90 (revision 28c427e5c022634ef479a98dc46291067a8c6c96)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2!Test for checking data constraints, C882-C887
3module m1
4  type person
5    integer :: age
6    character(len=25) :: name
7  end type
8  integer, parameter::digits(5) = ( /-11,-22,-33,44,55/ )
9  integer ::notConstDigits(5)
10  real, parameter::numbers(5) = ( /-11.11,-22.22,-33.33,44.44,55.55/ )
11  integer, parameter :: repeat = -1
12  integer :: myAge = 2
13  type(person) associated
14  type hasAlloc
15    integer, allocatable :: a
16  end type
17end
18
19subroutine CheckRepeat
20  use m1
21  type(person) myName(6)
22  !C882
23  !ERROR: Missing initialization for parameter 'uninitialized'
24  integer, parameter :: uninitialized
25  !C882
26  !ERROR: Repeat count (-1) for data value must not be negative
27  DATA myName(1)%age / repeat * 35 /
28  !C882
29  !ERROR: Repeat count (-11) for data value must not be negative
30  DATA myName(2)%age / digits(1) * 35 /
31  !C882
32  !ERROR: Must be a constant value
33  DATA myName(3)%age / repet * 35 /
34  !C885
35  !ERROR: Must have INTEGER type, but is REAL(4)
36  DATA myName(4)%age / numbers(1) * 35 /
37  !C886
38  !ERROR: Must be a constant value
39  DATA myName(5)%age / notConstDigits(1) * 35 /
40  !C887
41  !ERROR: Must be a constant value
42  DATA myName(6)%age / digits(myAge) * 35 /
43end
44
45subroutine CheckValue
46  use m1
47  !ERROR: USE-associated object 'associated' must not be initialized in a DATA statement
48  data associated / person(1, 'Abcd Ijkl') /
49  type(person) myName(3)
50  !OK: constant structure constructor
51  data myname(1) / person(1, 'Abcd Ijkl') /
52  !C883
53  !ERROR: 'persn' must be an array or structure constructor if used with non-empty parentheses as a DATA statement constant
54  data myname(2) / persn(2, 'Abcd Efgh') /
55  !C884
56  !ERROR: DATA statement value 'person(age=myage,name="Abcd Ijkl                ")' for 'myname(3_8)%age' is not a constant
57  data myname(3) / person(myAge, 'Abcd Ijkl') /
58  integer, parameter :: a(5) =(/11, 22, 33, 44, 55/)
59  integer :: b(5) =(/11, 22, 33, 44, 55/)
60  integer :: i
61  integer :: x, y, z
62  !OK: constant array element
63  data x / a(1) /
64  !C886, C887
65  !ERROR: DATA statement value 'a(int(i,kind=8))' for 'y' is not a constant
66  data y / a(i) /
67  !ERROR: DATA statement value 'b(1_8)' for 'z' is not a constant
68  data z / b(1) /
69  type(hasAlloc) ha
70  !ERROR: DATA statement value 'hasalloc(a=0_4)' for 'ha%a' is not a constant
71  data ha / hasAlloc(0) /
72end
73