Files
clang-p2996/flang/test/Semantics/array-constr-values.f90
peter klausler 3265b93363 [flang] Extension: reduced scope for some implied DO loop indices
The index of an implied DO loop in a DATA statement or array
constructor is defined by Fortran 2018 to have scope over its
implied DO loop.  This definition is unfortunate, because it
requires the implied DO loop's bounds expressions to be in the
scope of the index variable.  Consequently, in code like

  integer, parameter :: j = 5
  real, save :: a(5) = [(j, j=1, j)]

the upper bound of the loop is a reference to the index variable,
not the parameter in the enclosing scope.

This patch limits the scope of the index variable to the "body"
of the implied DO loop as one would naturally expect, with a warning.
I would have preferred to make this a hard error, but most Fortran
compilers treat this case as f18 now does.  If the standard
were to be fixed, the warning could be made optional.

Differential Revision: https://reviews.llvm.org/D108595
2021-08-24 09:34:18 -07:00

95 lines
3.9 KiB
Fortran

! RUN: %S/test_errors.sh %s %t %flang_fc1
! REQUIRES: shell
! Confirm enforcement of constraints and restrictions in 7.8
! C7110, C7111, C7112, C7113, C7114, C7115
subroutine arrayconstructorvalues()
integer :: intarray(5)
integer(KIND=8) :: k8 = 20
TYPE EMPLOYEE
INTEGER AGE
CHARACTER (LEN = 30) NAME
END TYPE EMPLOYEE
TYPE EMPLOYEER
CHARACTER (LEN = 30) NAME
END TYPE EMPLOYEER
TYPE(EMPLOYEE) :: emparray(3)
class(*), pointer :: unlim_polymorphic
TYPE, ABSTRACT :: base_type
INTEGER :: CARPRIZE
END TYPE
! Different declared type
!ERROR: Values in array constructor must have the same declared type when no explicit type appears
intarray = (/ 1, 2, 3, 4., 5/) ! C7110
! Different kind type parameter
!ERROR: Values in array constructor must have the same declared type when no explicit type appears
intarray = (/ 1,2,3,4, k8 /) ! C7110
! C7111
!ERROR: Value in array constructor of type 'LOGICAL(4)' could not be converted to the type of the array 'INTEGER(4)'
intarray = [integer:: .true., 2, 3, 4, 5]
!ERROR: Value in array constructor of type 'CHARACTER(1)' could not be converted to the type of the array 'INTEGER(4)'
intarray = [integer:: "RAM stores information", 2, 3, 4, 5]
!ERROR: Value in array constructor of type 'employee' could not be converted to the type of the array 'INTEGER(4)'
intarray = [integer:: EMPLOYEE (19, "Jack"), 2, 3, 4, 5]
! C7112
!ERROR: Value in array constructor of type 'INTEGER(4)' could not be converted to the type of the array 'employee'
emparray = (/ EMPLOYEE:: EMPLOYEE(19, "Ganesh"), EMPLOYEE(22, "Omkar"), 19 /)
!ERROR: Value in array constructor of type 'employeer' could not be converted to the type of the array 'employee'
emparray = (/ EMPLOYEE:: EMPLOYEE(19, "Ganesh"), EMPLOYEE(22, "Ram"),EMPLOYEER("ShriniwasPvtLtd") /)
! C7113
!ERROR: Cannot have an unlimited polymorphic value in an array constructor
intarray = (/ unlim_polymorphic, 2, 3, 4, 5/)
! C7114
!ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches operand types INTEGER(4) and TYPE(base_type)
!ERROR: ABSTRACT derived type 'base_type' may not be used in a structure constructor
!ERROR: Values in array constructor must have the same declared type when no explicit type appears
intarray = (/ base_type(10), 2, 3, 4, 5 /)
!ERROR: Item is not suitable for use in an array constructor
intarray(1:1) = [ arrayconstructorvalues ]
end subroutine arrayconstructorvalues
subroutine checkC7115()
real, dimension(10), parameter :: good1 = [(99.9, i = 1, 10)]
real, dimension(100), parameter :: good2 = [((88.8, i = 1, 10), j = 1, 10)]
real, dimension(-1:0), parameter :: good3 = [77.7, 66.6]
!ERROR: Implied DO index 'i' is active in a surrounding implied DO loop and may not have the same name
real, dimension(100), parameter :: bad = [((88.8, i = 1, 10), i = 1, 10)]
!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
!ERROR: The stride of an implied DO loop must not be zero
integer, parameter :: bad2(*) = [(j, j=1,1,0)]
integer, parameter, dimension(-1:0) :: negLower = (/343,512/)
integer, parameter, dimension(-1:0) :: negLower1 = ((/343,512/))
real :: local
local = good3(0)
!ERROR: Subscript value (2) is out of range on dimension 1 in reference to a constant array value
local = good3(2)
call inner(negLower(:)) ! OK
call inner(negLower1(:)) ! OK
contains
subroutine inner(arg)
integer :: arg(:)
end subroutine inner
end subroutine checkC7115
subroutine checkOkDuplicates
real :: realArray(21) = &
[ ((1.0, iDuplicate = 1,j), &
(0.0, iDuplicate = j,3 ), &
j = 1,5 ) ]
end subroutine
subroutine charLengths(c, array)
character(3) :: c
character(3) :: array(2)
!No error should ensue for distinct but compatible DynamicTypes
array = ["abc", c]
end subroutine