1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Confirm enforcement of constraints and restrictions in 7.8
3 ! C7110, C7111, C7112, C7113, C7114, C7115
5 subroutine arrayconstructorvalues()
7 integer(KIND
=8) :: k8
= 20
11 CHARACTER (LEN
= 30) NAME
14 CHARACTER (LEN
= 30) NAME
17 TYPE(EMPLOYEE
) :: emparray(3)
18 class(*), pointer :: unlim_polymorphic
19 TYPE, ABSTRACT
:: base_type
22 ! Different declared type
23 !ERROR: Values in array constructor must have the same declared type when no explicit type appears
24 intarray
= (/ 1, 2, 3, 4., 5/) ! C7110
25 ! Different kind type parameter
26 !ERROR: Values in array constructor must have the same declared type when no explicit type appears
27 intarray
= (/ 1,2,3,4, k8
/) ! C7110
30 !ERROR: Value in array constructor of type 'LOGICAL(4)' could not be converted to the type of the array 'INTEGER(4)'
31 intarray
= [integer:: .true
., 2, 3, 4, 5]
32 !ERROR: Value in array constructor of type 'CHARACTER(KIND=1,LEN=22_8)' could not be converted to the type of the array 'INTEGER(4)'
33 intarray
= [integer:: "RAM stores information", 2, 3, 4, 5]
34 !ERROR: Value in array constructor of type 'employee' could not be converted to the type of the array 'INTEGER(4)'
35 intarray
= [integer:: EMPLOYEE (19, "Jack"), 2, 3, 4, 5]
38 !ERROR: Value in array constructor of type 'INTEGER(4)' could not be converted to the type of the array 'employee'
39 emparray
= (/ EMPLOYEE
:: EMPLOYEE(19, "Ganesh"), EMPLOYEE(22, "Omkar"), 19 /)
40 !ERROR: Value in array constructor of type 'employeer' could not be converted to the type of the array 'employee'
41 emparray
= (/ EMPLOYEE
:: EMPLOYEE(19, "Ganesh"), EMPLOYEE(22, "Ram"),EMPLOYEER("ShriniwasPvtLtd") /)
44 !ERROR: Cannot have an unlimited polymorphic value in an array constructor
45 intarray
= (/ unlim_polymorphic
, 2, 3, 4, 5/)
48 !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches operand types INTEGER(4) and TYPE(base_type)
49 !ERROR: ABSTRACT derived type 'base_type' may not be used in a structure constructor
50 !ERROR: Values in array constructor must have the same declared type when no explicit type appears
51 intarray
= (/ base_type(10), 2, 3, 4, 5 /)
53 !ERROR: Item is not suitable for use in an array constructor
54 intarray(1:1) = [ arrayconstructorvalues
]
55 end subroutine arrayconstructorvalues
56 subroutine checkC7115()
57 real, dimension(10), parameter :: good1
= [(99.9, i
= 1, 10)]
58 real, dimension(100), parameter :: good2
= [((88.8, i
= 1, 10), j
= 1, 10)]
59 real, dimension(-1:0), parameter :: good3
= [77.7, 66.6]
60 !ERROR: Implied DO index 'i' is active in a surrounding implied DO loop and may not have the same name
61 real, dimension(100), parameter :: bad
= [((88.8, i
= 1, 10), i
= 1, 10)]
63 !ERROR: Value of named constant 'bad2' ([INTEGER(4)::(int(j,kind=4),INTEGER(8)::j=1_8,1_8,0_8)]) cannot be computed as a constant value
64 !ERROR: The stride of an implied DO loop must not be zero
65 integer, parameter :: bad2(*) = [(j
, j
=1,1,0)]
66 integer, parameter, dimension(-1:0) :: negLower
= (/343,512/)
67 integer, parameter, dimension(-1:0) :: negLower1
= ((/343,512/))
72 !ERROR: Subscript value (2) is out of range on dimension 1 in reference to a constant array value
74 call inner(negLower(:)) ! OK
75 call inner(negLower1(:)) ! OK
81 end subroutine checkC7115
82 subroutine checkOkDuplicates
83 real :: realArray(21) = &
84 [ ((1.0, iDuplicate
= 1,j
), &
85 (0.0, iDuplicate
= j
,3 ), &
88 subroutine charLengths(c
, array
)
90 character(3) :: array(2)
91 !No error should ensue for distinct but compatible DynamicTypes