llvm-project/flang/test/Semantics/array-constr-values.f90

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

86 lines
3.6 KiB
Fortran
Raw Normal View History

! RUN: %S/test_errors.sh %s %t %f18
! 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
!ERROR: Values in array constructor must have the same declared type when no explicit type appears
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 /)
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)]
[flang] Fix problems with constant arrays with lower bounds that are not 1 There were two problems with constant arrays whose lower bound is not 1. First, when folding the arrays, we were creating the folded array to have lower bounds of 1 but, we were not re-adjusting their lower bounds to the declared values. Second, we were not calculating the extents correctly. Both of these problems led to bogus error messages. I fixed the first problem by adjusting the lower bounds in NonPointerInitializationExpr() in Evaluate/check-expression.cpp. I wrote the class ArrayConstantBoundChanger, which is similar to the existing class ScalarConstantExpander. In the process of implementing and testing it, I found a bug that I fixed in ScalarConstantExpander which caused it to infinitely recurse on parenthesized expressions. I also removed the unrelated class ScalarExpansionVisitor, which was not used. I fixed the second problem by changing the formula that calculates upper bounds in in the function ComputeUpperBound() in Evaluate/shape.cpp. I added tests that trigger the bogus error messages mentioned above along with a constant folding tests that uses array operands with shapes that conform but have different bounds. In the process of adding tests, I discovered that tests in Evaluate/folding09.f90 and folding16.f90 were written incorrectly, and I fixed them. This also revealed a bug in contant folding of the intrinsic "lbounds" which I plan to fix in a later change. Differential Revision: https://reviews.llvm.org/D95449
2021-01-27 00:20:57 +08:00
real, dimension(-1:0), parameter :: good3 = [77.7, 66.6]
!ERROR: Implied DO index is active in surrounding implied DO loop and may not have the same name
real, dimension(100), parameter :: bad = [((88.8, i = 1, 10), i = 1, 10)]
[flang] Improve initializer semantics, esp. for component default values This patch plugs many holes in static initializer semantics, improves error messages for default initial values and other component properties in parameterized derived type instantiations, and cleans up several small issues noticed during development. We now do proper scalar expansion, folding, and type, rank, and shape conformance checking for component default initializers in derived types and PDT instantiations. The initial values of named constants are now guaranteed to have been folded when installed in the symbol table, and are no longer folded or scalar-expanded at each use in expression folding. Semantics documentation was extended with information about the various kinds of initializations in Fortran and when each of them are processed in the compiler. Some necessary concomitant changes have bulked this patch out a bit: * contextual messages attachments, which are now produced for parameterized derived type instantiations so that the user can figure out which instance caused a problem with a component, have been added as part of ContextualMessages, and their implementation was debugged * several APIs in evaluate::characteristics was changed so that a FoldingContext is passed as an argument rather than just its intrinsic procedure table; this affected client call sites in many files * new tools in Evaluate/check-expression.cpp to determine when an Expr actually is a single constant value and to validate a non-pointer variable initializer or object component default value * shape conformance checking has additional arguments that control whether scalar expansion is allowed * several now-unused functions and data members noticed and removed * several crashes and bogus errors exposed by testing this new code were fixed * a -fdebug-stack-trace option to enable LLVM's stack tracing on a crash, which might be useful in the future TL;DR: Initialization processing does more and takes place at the right times for all of the various kinds of things that can be initialized. Differential Review: https://reviews.llvm.org/D92783
2020-12-08 04:08:58 +08:00
!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)]
[flang] Fix problems with constant arrays with lower bounds that are not 1 There were two problems with constant arrays whose lower bound is not 1. First, when folding the arrays, we were creating the folded array to have lower bounds of 1 but, we were not re-adjusting their lower bounds to the declared values. Second, we were not calculating the extents correctly. Both of these problems led to bogus error messages. I fixed the first problem by adjusting the lower bounds in NonPointerInitializationExpr() in Evaluate/check-expression.cpp. I wrote the class ArrayConstantBoundChanger, which is similar to the existing class ScalarConstantExpander. In the process of implementing and testing it, I found a bug that I fixed in ScalarConstantExpander which caused it to infinitely recurse on parenthesized expressions. I also removed the unrelated class ScalarExpansionVisitor, which was not used. I fixed the second problem by changing the formula that calculates upper bounds in in the function ComputeUpperBound() in Evaluate/shape.cpp. I added tests that trigger the bogus error messages mentioned above along with a constant folding tests that uses array operands with shapes that conform but have different bounds. In the process of adding tests, I discovered that tests in Evaluate/folding09.f90 and folding16.f90 were written incorrectly, and I fixed them. This also revealed a bug in contant folding of the intrinsic "lbounds" which I plan to fix in a later change. Differential Revision: https://reviews.llvm.org/D95449
2021-01-27 00:20:57 +08:00
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