xref: /llvm-project/flang/test/Semantics/array-constr-values.f90 (revision 6c09a9bf6c6247299b53833602e6bb312dfda555)
16c1ac141SIvan Zhechev! RUN: %python %S/test_errors.py %s %flang_fc1
249660234Ssameeran joshi! Confirm enforcement of constraints and restrictions in 7.8
349660234Ssameeran joshi! C7110, C7111, C7112, C7113, C7114, C7115
449660234Ssameeran joshi
549660234Ssameeran joshisubroutine arrayconstructorvalues()
675f9b189SPeter Klausler  integer :: intarray(4)
749660234Ssameeran joshi  integer(KIND=8) :: k8 = 20
849660234Ssameeran joshi
949660234Ssameeran joshi  TYPE EMPLOYEE
1049660234Ssameeran joshi    INTEGER AGE
1149660234Ssameeran joshi    CHARACTER (LEN = 30) NAME
1249660234Ssameeran joshi  END TYPE EMPLOYEE
1349660234Ssameeran joshi  TYPE EMPLOYEER
1449660234Ssameeran joshi    CHARACTER (LEN = 30) NAME
1549660234Ssameeran joshi  END TYPE EMPLOYEER
1649660234Ssameeran joshi
1749660234Ssameeran joshi  TYPE(EMPLOYEE) :: emparray(3)
1849660234Ssameeran joshi  class(*), pointer :: unlim_polymorphic
1949660234Ssameeran joshi  TYPE, ABSTRACT :: base_type
2049660234Ssameeran joshi    INTEGER :: CARPRIZE
2149660234Ssameeran joshi  END TYPE
2249660234Ssameeran joshi  ! Different declared type
2349660234Ssameeran joshi  !ERROR: Values in array constructor must have the same declared type when no explicit type appears
2449660234Ssameeran joshi  intarray = (/ 1, 2, 3, 4., 5/)  ! C7110
2549660234Ssameeran joshi  ! Different kind type parameter
2649660234Ssameeran joshi  !ERROR: Values in array constructor must have the same declared type when no explicit type appears
2749660234Ssameeran joshi  intarray = (/ 1,2,3,4, k8 /)    ! C7110
2849660234Ssameeran joshi
2949660234Ssameeran joshi  ! C7111
3049660234Ssameeran joshi  !ERROR: Value in array constructor of type 'LOGICAL(4)' could not be converted to the type of the array 'INTEGER(4)'
3149660234Ssameeran joshi  intarray = [integer:: .true., 2, 3, 4, 5]
32ae93d8eaSPeter Klausler  !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)'
3349660234Ssameeran joshi  intarray = [integer:: "RAM stores information", 2, 3, 4, 5]
3449660234Ssameeran joshi  !ERROR: Value in array constructor of type 'employee' could not be converted to the type of the array 'INTEGER(4)'
3549660234Ssameeran joshi  intarray = [integer:: EMPLOYEE (19, "Jack"), 2, 3, 4, 5]
3649660234Ssameeran joshi
3749660234Ssameeran joshi  ! C7112
38*6c09a9bfSPeter Klausler  !ERROR: Dimension 1 of left-hand side has extent 3, but right-hand side has extent 2
3949660234Ssameeran joshi  !ERROR: Value in array constructor of type 'INTEGER(4)' could not be converted to the type of the array 'employee'
4049660234Ssameeran joshi  emparray = (/ EMPLOYEE:: EMPLOYEE(19, "Ganesh"), EMPLOYEE(22, "Omkar"), 19 /)
41*6c09a9bfSPeter Klausler  !ERROR: Dimension 1 of left-hand side has extent 3, but right-hand side has extent 2
4249660234Ssameeran joshi  !ERROR: Value in array constructor of type 'employeer' could not be converted to the type of the array 'employee'
4349660234Ssameeran joshi  emparray = (/ EMPLOYEE:: EMPLOYEE(19, "Ganesh"), EMPLOYEE(22, "Ram"),EMPLOYEER("ShriniwasPvtLtd") /)
4449660234Ssameeran joshi
4549660234Ssameeran joshi  ! C7113
4649660234Ssameeran joshi  !ERROR: Cannot have an unlimited polymorphic value in an array constructor
4749660234Ssameeran joshi  intarray = (/ unlim_polymorphic, 2, 3, 4, 5/)
4849660234Ssameeran joshi
49e7cb6778SPeter Klausler  ! C7114, F'2023 C7125
5049660234Ssameeran joshi  !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches operand types INTEGER(4) and TYPE(base_type)
5149660234Ssameeran joshi  !ERROR: ABSTRACT derived type 'base_type' may not be used in a structure constructor
52e7cb6778SPeter Klausler  !ERROR: An item whose declared type is ABSTRACT may not appear in an array constructor
5349660234Ssameeran joshi  !ERROR: Values in array constructor must have the same declared type when no explicit type appears
5449660234Ssameeran joshi  intarray = (/ base_type(10), 2, 3, 4, 5 /)
55ec3049c7Speter klausler
56ec3049c7Speter klausler  !ERROR: Item is not suitable for use in an array constructor
57ec3049c7Speter klausler  intarray(1:1) = [ arrayconstructorvalues ]
5849660234Ssameeran joshiend subroutine arrayconstructorvalues
5949660234Ssameeran joshisubroutine checkC7115()
6049660234Ssameeran joshi  real, dimension(10), parameter :: good1 = [(99.9, i = 1, 10)]
6149660234Ssameeran joshi  real, dimension(100), parameter :: good2 = [((88.8, i = 1, 10), j = 1, 10)]
62543cd89dSPeter Steinfeld  real, dimension(-1:0), parameter :: good3 = [77.7, 66.6]
633265b933Speter klausler  !ERROR: Implied DO index 'i' is active in a surrounding implied DO loop and may not have the same name
6449660234Ssameeran joshi  real, dimension(100), parameter :: bad = [((88.8, i = 1, 10), i = 1, 10)]
65e8f96899Speter klausler
66641ede93Speter klausler  !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
67e8f96899Speter klausler  !ERROR: The stride of an implied DO loop must not be zero
68e8f96899Speter klausler  integer, parameter :: bad2(*) = [(j, j=1,1,0)]
69543cd89dSPeter Steinfeld  integer, parameter, dimension(-1:0) :: negLower = (/343,512/)
70543cd89dSPeter Steinfeld  integer, parameter, dimension(-1:0) :: negLower1 = ((/343,512/))
71543cd89dSPeter Steinfeld
72543cd89dSPeter Steinfeld  real :: local
73543cd89dSPeter Steinfeld
74543cd89dSPeter Steinfeld  local = good3(0)
75543cd89dSPeter Steinfeld  !ERROR: Subscript value (2) is out of range on dimension 1 in reference to a constant array value
76543cd89dSPeter Steinfeld  local = good3(2)
77543cd89dSPeter Steinfeld  call inner(negLower(:)) ! OK
78543cd89dSPeter Steinfeld  call inner(negLower1(:)) ! OK
79543cd89dSPeter Steinfeld
80543cd89dSPeter Steinfeld  contains
81543cd89dSPeter Steinfeld    subroutine inner(arg)
82543cd89dSPeter Steinfeld      integer :: arg(:)
83543cd89dSPeter Steinfeld    end subroutine inner
8449660234Ssameeran joshiend subroutine checkC7115
85681978d3SPeter Steinfeldsubroutine checkOkDuplicates
86681978d3SPeter Steinfeld  real :: realArray(21) = &
87681978d3SPeter Steinfeld    [ ((1.0, iDuplicate = 1,j), &
88681978d3SPeter Steinfeld       (0.0, iDuplicate = j,3 ), &
89681978d3SPeter Steinfeld        j = 1,5 ) ]
90681978d3SPeter Steinfeldend subroutine
91ac964175Speter klauslersubroutine charLengths(c, array)
92ac964175Speter klausler  character(3) :: c
93ac964175Speter klausler  character(3) :: array(2)
94ac964175Speter klausler  !No error should ensue for distinct but compatible DynamicTypes
95ac964175Speter klausler  array = ["abc", c]
96ac964175Speter klauslerend subroutine
97