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

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

76 lines
1.7 KiB
Fortran
Raw Normal View History

! RUN: %S/test_modfile.sh %s %t %f18
! Test declarations with coarray-spec
! Different ways of declaring the same coarray.
module m1
real :: a(1:5)[1:10,1:*]
real, dimension(5) :: b[1:10,1:*]
real, codimension[1:10,1:*] :: c(5)
real, codimension[1:10,1:*], dimension(5) :: d
codimension :: e[1:10,1:*]
dimension :: e(5)
real :: e
end
!Expect: m1.mod
!module m1
! real(4)::a(1_8:5_8)[1_8:10_8,1_8:*]
! real(4)::b(1_8:5_8)[1_8:10_8,1_8:*]
! real(4)::c(1_8:5_8)[1_8:10_8,1_8:*]
! real(4)::d(1_8:5_8)[1_8:10_8,1_8:*]
! real(4)::e(1_8:5_8)[1_8:10_8,1_8:*]
!end
! coarray-spec in codimension and target statements.
module m2
codimension :: a[10,*], b[*]
target :: c[10,*], d[*]
end
!Expect: m2.mod
!module m2
! real(4)::a[1_8:10_8,1_8:*]
! real(4)::b[1_8:*]
! real(4),target::c[1_8:10_8,1_8:*]
! real(4),target::d[1_8:*]
!end
! coarray-spec in components and with non-constants bounds
module m3
type t
[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
real, allocatable :: c[:,:]
complex, allocatable, codimension[:,:] :: d
end type
real, allocatable :: e[:,:,:]
contains
subroutine s(a, b, n)
integer(8) :: n
real :: a[1:n,2:*]
real, codimension[1:n,2:*] :: b
end
end
!Expect: m3.mod
!module m3
! type::t
[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
! real(4),allocatable::c[:,:]
! complex(4),allocatable::d[:,:]
! end type
! real(4),allocatable::e[:,:,:]
!contains
! subroutine s(a,b,n)
! integer(8)::n
! real(4)::a[1_8:n,2_8:*]
! real(4)::b[1_8:n,2_8:*]
! end
!end
! coarray-spec in both attributes and entity-decl
module m4
real, codimension[2:*], dimension(2:5) :: a, b(4,4), c[10,*], d(4,4)[10,*]
end
!Expect: m4.mod
!module m4
! real(4)::a(2_8:5_8)[2_8:*]
! real(4)::b(1_8:4_8,1_8:4_8)[2_8:*]
! real(4)::c(2_8:5_8)[1_8:10_8,1_8:*]
! real(4)::d(1_8:4_8,1_8:4_8)[1_8:10_8,1_8:*]
!end