llvm-project/flang/test/Semantics/allocate11.f90

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

162 lines
6.8 KiB
Fortran
Raw Normal View History

[flang] A rework of the cmake build components for in and out of tree builds. In general all the basic functionality seems to work and removes some redundancy and more complicated features in favor of borrowing infrastructure from LLVM build configurations. Here's a quick summary of details and remaining issues: * Testing has spanned Ubuntu 18.04 & 19.10, CentOS 7, RHEL 8, and MacOS/darwin. Architectures include x86_64 and Arm. Without access to Window nothing has been tested there yet. * As we change file and directory naming schemes (i.e., capitalization) some odd things can occur on MacOS systems with case preserving but not case senstive file system configurations. Can be painful and certainly something to watch out for as any any such changes continue. * Testing infrastructure still needs to be tuned up and worked on. Note that there do appear to be cases of some tests hanging (on MacOS in particular). They appear unrelated to the build process. * Shared library configurations need testing (and probably fixing). * Tested both standalone and 'in-mono repo' builds. Changes for supporting the mono repo builds will require LLVM-level changes that are straightforward when the time comes. * The configuration contains a work-around for LLVM's C++ standard mode passing down into Flang/F18 builds (i.e., LLVM CMake configuration would force a -std=c++11 flag to show up in command line arguments. The current configuration removes that automatically and is more strict in following new CMake guidelines for enforcing C++17 mode across all the CMake files. * Cleaned up a lot of repetition in the command line arguments. It is likely that more work is still needed to both allow for customization and working around CMake defailts (or those inherited from LLVM's configuration files). On some platforms agressive optimization flags (e.g. -O3) can actually break builds due to the inlining of templates in .cpp source files that then no longer are available for use cases outside those source files (shows up as link errors). Sticking at -O2 appears to fix this. Currently this CMake configuration forces this in release mode but at the cost of stomping on any CMake, or user customized, settings for the release flags. * Made the lit tests non-source directory dependent where appropriate. This is done by configuring certain test shell files to refer to the correct paths whether an in or out of tree build is being performed. These configured files are output in the build directory. A %B substitution is introduced in lit to refer to the build directory, mirroring the %S substitution for the source directory, so that the tests can refer to the configured shell scripts. Co-authored-by: David Truby <david.truby@arm.com> Original-commit: flang-compiler/f18@d1c7184159b2d3c542a8f36c58a0c817e7506845 Reviewed-on: https://github.com/flang-compiler/f18/pull/1045
2020-02-26 07:22:14 +08:00
! RUN: %B/test/Semantics/test_errors.sh %s %flang %t
! Check for semantic errors in ALLOCATE statements
! TODO: Function Pointer in allocate and derived types!
! Rules I should know when working with coarrays and derived type:
! C736: If EXTENDS appears and the type being defined has a coarray ultimate
! component, its parent type shall have a coarray ultimate component.
! C746: (R737) If a coarray-spec appears, it shall be a deferred-coshape-spec-list
! and the component shall have the ALLOCATABLE attribute.
! C747: If a coarray-spec appears, the component shall not be of type C_PTR or
! C_FUNPTR from the intrinsic module ISO_C_BINDING (18.2), or of type TEAM_TYPE from the
! intrinsic module ISO_FORTRAN_ENV (16.10.2).
! C748: A data component whose type has a coarray ultimate component shall be a
! nonpointer nonallocatable scalar and shall not be a coarray.
! 7.5.4.3 Coarray components
! 7.5.6 Final subroutines: C786
! C825 An entity whose type has a coarray ultimate component shall be a
! nonpointer nonallocatable scalar, shall not be a coarray, and shall not be a function result.
! C826 A coarray or an object with a coarray ultimate component shall be an
! associate name, a dummy argument, or have the ALLOCATABLE or SAVE attribute.
subroutine C937(var)
! Type-spec shall not specify a type that has a coarray ultimate component.
type A
real, allocatable :: x[:]
end type
type B
type(A) y
[flang] New implementation for checks for constraints C741 through C750 Summary: Most of these checks were already implemented, and I just added references to them to the code and tests. Also, much of this code was already reviewed in the old flang/f18 GitHub repository, but I didn't get to merge it before we switched repositories. I implemented the check for C747 to not allow coarray components in derived types that are of type C_PTR, C_FUNPTR, or type TEAM_TYPE. I implemented the check for C748 that requires a data component whose type has a coarray ultimate component to be a nonpointer, nonallocatable scalar and not be a coarray. I implemented the check for C750 that adds additional restrictions to the bounds expressions of a derived type component that's an array. These bounds expressions are sepcification expressions as defined in 10.1.11. There was already code in lib/Evaluate/check-expression.cpp to check semantics for specification expressions, but it did not check for the extra requirements of C750. C750 prohibits specification functions, the intrinsic functions ALLOCATED, ASSOCIATED, EXTENDS_TYPE_OF, PRESENT, and SAME_TYPE_AS. It also requires every specification inquiry reference to be a constant expression, and requires that the value of the bound not depend on the value of a variable. To implement these additional checks, I added code to the intrinsic proc table to get the intrinsic class of a procedure. I also added an enumeration to distinguish between specification expressions for derived type component bounds versus for type parameters. I then changed the code to pass an enumeration value to "CheckSpecificationExpr()" to indicate that the expression was a bounds expression and used this value to determine whether to emit an error message when violations of C750 are found. I changed the implementation of IsPureProcedure() to handle statement functions and changed some references in the code that tested for the PURE attribute to call IsPureProcedure(). I also fixed some unrelated tests that got new errors when I implemented these new checks. Reviewers: tskeith, DavidTruby, sscalpone Subscribers: jfb, llvm-commits Tags: #llvm, #flang Differential Revision: https://reviews.llvm.org/D79263
2020-05-02 04:00:28 +08:00
!ERROR: A component with a POINTER or ALLOCATABLE attribute may not be of a type with a coarray ultimate component (named 'y%x')
type(B), pointer :: forward
real :: u
end type
type C
type(B) z
end type
type D
[flang] New implementation for checks for constraints C741 through C750 Summary: Most of these checks were already implemented, and I just added references to them to the code and tests. Also, much of this code was already reviewed in the old flang/f18 GitHub repository, but I didn't get to merge it before we switched repositories. I implemented the check for C747 to not allow coarray components in derived types that are of type C_PTR, C_FUNPTR, or type TEAM_TYPE. I implemented the check for C748 that requires a data component whose type has a coarray ultimate component to be a nonpointer, nonallocatable scalar and not be a coarray. I implemented the check for C750 that adds additional restrictions to the bounds expressions of a derived type component that's an array. These bounds expressions are sepcification expressions as defined in 10.1.11. There was already code in lib/Evaluate/check-expression.cpp to check semantics for specification expressions, but it did not check for the extra requirements of C750. C750 prohibits specification functions, the intrinsic functions ALLOCATED, ASSOCIATED, EXTENDS_TYPE_OF, PRESENT, and SAME_TYPE_AS. It also requires every specification inquiry reference to be a constant expression, and requires that the value of the bound not depend on the value of a variable. To implement these additional checks, I added code to the intrinsic proc table to get the intrinsic class of a procedure. I also added an enumeration to distinguish between specification expressions for derived type component bounds versus for type parameters. I then changed the code to pass an enumeration value to "CheckSpecificationExpr()" to indicate that the expression was a bounds expression and used this value to determine whether to emit an error message when violations of C750 are found. I changed the implementation of IsPureProcedure() to handle statement functions and changed some references in the code that tested for the PURE attribute to call IsPureProcedure(). I also fixed some unrelated tests that got new errors when I implemented these new checks. Reviewers: tskeith, DavidTruby, sscalpone Subscribers: jfb, llvm-commits Tags: #llvm, #flang Differential Revision: https://reviews.llvm.org/D79263
2020-05-02 04:00:28 +08:00
!ERROR: A component with a POINTER or ALLOCATABLE attribute may not be of a type with a coarray ultimate component (named 'x')
type(A), pointer :: potential
end type
class(*), allocatable :: var
! unlimited polymorphic is the ONLY way to get an allocatable/pointer 'var' that can be
! allocated with a type-spec T that has coarray ultimate component without
! violating other rules than C937.
! Rationale:
! C934 => var must be type compatible with T.
! => var type is T, a type P extended by T, or unlimited polymorphic
! C825 => var cannot be of type T.
! C736 => all parent types P of T must have a coarray ultimate component
! => var cannot be of type P (C825)
! => if var can be defined, it can only be unlimited polymorphic
! Also, as per C826 or C852, var can only be an allocatable, not a pointer
! OK, x is not an ultimate component
allocate(D:: var)
!ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
allocate(A:: var)
!ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
allocate(B:: var)
!ERROR: Type-spec in ALLOCATE must not specify a type with a coarray ultimate component
allocate(C:: var)
end subroutine
!TODO: type extending team_type !? subcomponents !?
subroutine C938_C947(var2, ptr, ptr2, fptr, my_team, srca)
! If an allocate-object is a coarray, type-spec shall not specify type C_PTR or
! C_FUNPTR from the intrinsic module ISO_C_BINDING, or type TEAM_TYPE from the intrinsic module
! ISO_FORTRAN_ENV.
use ISO_FORTRAN_ENV
use ISO_C_BINDING
type A(k, l)
integer, kind :: k
integer, len :: l
real(kind=k) x(l,l)
end type
! Again, I do not see any other way to violate this rule and not others without
! having var being an unlimited polymorphic.
! Suppose var of type P and T, the type in type-spec
! Per C934, P must be compatible with T. P cannot be a forbidden type per C824.
! Per C728 and 7.5.7.1, P cannot extend a c_ptr or _c_funptr. hence, P has to be
! unlimited polymorphic or a type that extends TEAM_TYPE.
class(*), allocatable :: var[:], var2(:)[:]
class(*), allocatable :: varok, varok2(:)
Type(C_PTR) :: ptr, ptr2(2:10)
Type(C_FUNPTR) fptr
Type(TEAM_TYPE) my_team
Type(A(4, 10)) :: srca
! Valid constructs
allocate(real:: var[5:*])
allocate(A(4, 10):: var[5:*])
allocate(TEAM_TYPE:: varok, varok2(2))
allocate(C_PTR:: varok, varok2(2))
allocate(C_FUNPTR:: varok, varok2(2))
!ERROR: Type-Spec in ALLOCATE must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
allocate(TEAM_TYPE:: var[5:*])
!ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(C_PTR:: varok, var[5:*])
!ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(C_FUNPTR:: var[5:*])
!ERROR: Type-Spec in ALLOCATE must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
allocate(TEAM_TYPE:: var2(2)[5:*])
!ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(C_PTR:: var2(2)[5:*])
!ERROR: Type-Spec in ALLOCATE must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(C_FUNPTR:: varok2(2), var2(2)[5:*])
! C947: The declared type of source-expr shall not be C_PTR or C_FUNPTR from the
! intrinsic module ISO_C_BINDING, or TEAM_TYPE from the intrinsic module
! ISO_FORTRAN_ENV, if an allocateobject is a coarray.
!
! ! Valid constructs
allocate(var[5:*], SOURCE=cos(0.5_4))
allocate(var[5:*], MOLD=srca)
allocate(varok, varok2(2), SOURCE=ptr)
allocate(varok2, MOLD=ptr2)
allocate(varok, varok2(2), SOURCE=my_team)
allocate(varok, varok2(2), MOLD=fptr)
!ERROR: SOURCE or MOLD expression type must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
allocate(var[5:*], SOURCE=my_team)
!ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(var[5:*], SOURCE=ptr)
!ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(varok, var[5:*], MOLD=ptr2(1))
!ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(var[5:*], MOLD=fptr)
!ERROR: SOURCE or MOLD expression type must not be TEAM_TYPE from ISO_FORTRAN_ENV when an allocatable object is a coarray
allocate(var2(2)[5:*], MOLD=my_team)
!ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(var2(2)[5:*], MOLD=ptr)
!ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(var2(2)[5:*], SOURCE=ptr2)
!ERROR: SOURCE or MOLD expression type must not be C_PTR or C_FUNPTR from ISO_C_BINDING when an allocatable object is a coarray
allocate(varok2(2), var2(2)[5:*], SOURCE=fptr)
end subroutine