Skip to content

Commit b4ce919

Browse files
rasmussnjeanPerier
authored andcommitted
[flang] Make 'this_image()' an intrinsic function
Added 'this_image()' to the list of functions that are evaluated as intrinsic. Added IsCoarray functions to determine if an expression is a coarray (corank > 1). Added save attribute to coarray variables in test file, this_image.f90. reviewers: klausler, PeteSteinfeld Differential Revision: https://reviews.llvm.org/D108059
1 parent abe21a1 commit b4ce919

File tree

6 files changed

+65
-4
lines changed

6 files changed

+65
-4
lines changed

flang/docs/Intrinsics.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -746,7 +746,7 @@ This phase currently supports all the intrinsic procedures listed above but the
746746

747747
| Intrinsic Category | Intrinsic Procedures Lacking Support |
748748
| --- | --- |
749-
| Coarray intrinsic functions | LCOBOUND, UCOBOUND, FAILED_IMAGES, GET_TEAM, IMAGE_INDEX, STOPPED_IMAGES, TEAM_NUMBER, THIS_IMAGE, COSHAPE |
749+
| Coarray intrinsic functions | LCOBOUND, UCOBOUND, FAILED_IMAGES, GET_TEAM, IMAGE_INDEX, STOPPED_IMAGES, TEAM_NUMBER, COSHAPE |
750750
| Object characteristic inquiry functions | ALLOCATED, ASSOCIATED, EXTENDS_TYPE_OF, IS_CONTIGUOUS, PRESENT, RANK, SAME_TYPE, STORAGE_SIZE |
751751
| Type inquiry intrinsic functions | BIT_SIZE, DIGITS, EPSILON, HUGE, KIND, MAXEXPONENT, MINEXPONENT, NEW_LINE, PRECISION, RADIX, RANGE, TINY|
752752
| Non-standard intrinsic functions | AND, OR, XOR, LSHIFT, RSHIFT, SHIFT, ZEXT, IZEXT, COSD, SIND, TAND, ACOSD, ASIND, ATAND, ATAN2D, COMPL, DCMPLX, EQV, NEQV, INT8, JINT, JNINT, KNINT, LOC, QCMPLX, DREAL, DFLOAT, QEXT, QFLOAT, QREAL, DNUM, NUM, JNUM, KNUM, QNUM, RNUM, RAN, RANF, ILEN, SIZEOF, MCLOCK, SECNDS, COTAN, IBCHNG, ISHA, ISHC, ISHL, IXOR, IARG, IARGC, NARGS, NUMARG, BADDRESS, IADDR, CACHESIZE, EOF, FP_CLASS, INT_PTR_KIND, ISNAN, MALLOC |

flang/include/flang/Evaluate/tools.h

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -89,6 +89,22 @@ template <typename A> bool IsAssumedRank(const std::optional<A> &x) {
8989
return x && IsAssumedRank(*x);
9090
}
9191

92+
// Predicate: true when an expression is a coarray (corank > 0)
93+
bool IsCoarray(const ActualArgument &);
94+
template <typename A> bool IsCoarray(const A &) { return false; }
95+
template <typename A> bool IsCoarray(const Designator<A> &designator) {
96+
if (const auto *symbol{std::get_if<SymbolRef>(&designator.u)}) {
97+
return symbol->get().Corank() > 0;
98+
}
99+
return false;
100+
}
101+
template <typename T> bool IsCoarray(const Expr<T> &expr) {
102+
return std::visit([](const auto &x) { return IsCoarray(x); }, expr.u);
103+
}
104+
template <typename A> bool IsCoarray(const std::optional<A> &x) {
105+
return x && IsCoarray(*x);
106+
}
107+
92108
// Generalizing packagers: these take operations and expressions of more
93109
// specific types and wrap them in Expr<> containers of more abstract types.
94110

flang/lib/Evaluate/intrinsics.cpp

Lines changed: 19 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@
1616
#include "flang/Evaluate/shape.h"
1717
#include "flang/Evaluate/tools.h"
1818
#include "flang/Evaluate/type.h"
19+
#include "flang/Semantics/tools.h"
1920
#include "llvm/Support/raw_ostream.h"
2021
#include <algorithm>
2122
#include <map>
@@ -176,6 +177,7 @@ ENUM_CLASS(Rank,
176177
shape, // INTEGER vector of known length and no negative element
177178
matrix,
178179
array, // not scalar, rank is known and greater than zero
180+
coarray, // rank is known and can be scalar; has nonzero corank
179181
known, // rank is known and can be scalar
180182
anyOrAssumedRank, // rank can be unknown; assumed-type TYPE(*) allowed
181183
conformable, // scalar, or array of same rank & shape as "array" argument
@@ -741,6 +743,12 @@ static const IntrinsicInterface genericIntrinsicFunction[]{
741743
{"tan", {{"x", SameFloating}}, SameFloating},
742744
{"tand", {{"x", SameFloating}}, SameFloating},
743745
{"tanh", {{"x", SameFloating}}, SameFloating},
746+
// optional team dummy arguments needed to complete the following
747+
// this_image versions
748+
{"this_image", {{"coarray", AnyData, Rank::coarray}, OptionalDIM},
749+
DefaultInt, Rank::scalar, IntrinsicClass::transformationalFunction},
750+
{"this_image", {}, DefaultInt, Rank::scalar,
751+
IntrinsicClass::transformationalFunction},
744752
{"tiny", {{"x", SameReal, Rank::anyOrAssumedRank}}, SameReal, Rank::scalar,
745753
IntrinsicClass::inquiryFunction},
746754
{"trailz", {{"i", AnyInt}}, DefaultInt},
@@ -814,8 +822,7 @@ static const IntrinsicInterface genericIntrinsicFunction[]{
814822

815823
// TODO: Coarray intrinsic functions
816824
// LCOBOUND, UCOBOUND, FAILED_IMAGES, GET_TEAM, IMAGE_INDEX,
817-
// STOPPED_IMAGES, TEAM_NUMBER, THIS_IMAGE,
818-
// COSHAPE
825+
// STOPPED_IMAGES, TEAM_NUMBER, COSHAPE
819826
// TODO: Non-standard intrinsic functions
820827
// AND, OR, XOR, LSHIFT, RSHIFT, SHIFT, ZEXT, IZEXT,
821828
// COMPL, EQV, NEQV, INT8, JINT, JNINT, KNINT,
@@ -1420,6 +1427,15 @@ std::optional<SpecificCall> IntrinsicInterface::Match(
14201427
argOk &= rank == arrayArg->Rank();
14211428
}
14221429
break;
1430+
case Rank::coarray:
1431+
argOk = IsCoarray(*arg);
1432+
if (!argOk) {
1433+
messages.Say(
1434+
"'coarray=' argument must have corank > 0 for intrinsic '%s'"_err_en_US,
1435+
name);
1436+
return std::nullopt;
1437+
}
1438+
break;
14231439
case Rank::known:
14241440
if (!knownArg) {
14251441
knownArg = arg;
@@ -1634,6 +1650,7 @@ std::optional<SpecificCall> IntrinsicInterface::Match(
16341650
case Rank::elementalOrBOZ:
16351651
case Rank::shape:
16361652
case Rank::array:
1653+
case Rank::coarray:
16371654
case Rank::known:
16381655
case Rank::anyOrAssumedRank:
16391656
case Rank::reduceOperation:

flang/lib/Evaluate/tools.cpp

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -683,6 +683,13 @@ bool IsAssumedRank(const ActualArgument &arg) {
683683
}
684684
}
685685

686+
bool IsCoarray(const ActualArgument &arg) {
687+
if (const auto *expr{arg.UnwrapExpr()}) {
688+
return IsCoarray(*expr);
689+
}
690+
return false;
691+
}
692+
686693
bool IsProcedure(const Expr<SomeType> &expr) {
687694
return std::holds_alternative<ProcedureDesignator>(expr.u);
688695
}

flang/test/Semantics/call10.f90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -184,7 +184,6 @@ pure subroutine s13
184184
pure subroutine s14
185185
integer :: img, nimgs, i[*], tmp
186186
! implicit sync all
187-
!ERROR: Procedure 'this_image' referenced in pure subprogram 's14' must be pure too
188187
img = this_image()
189188
nimgs = num_images()
190189
i = img ! i is ready to use

flang/test/Semantics/this_image.f90

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
! RUN: %python %S/test_errors.py %s %flang_fc1
2+
! Check for semantic errors in this_image() function calls
3+
4+
subroutine test
5+
use, intrinsic :: iso_fortran_env, only: team_type
6+
type(team_type) :: oregon, coteam[*]
7+
integer :: coscalar[*], coarray(3)[*]
8+
save :: coteam, coscalar, coarray
9+
10+
! correct calls, should produce no errors
11+
print *, this_image()
12+
print *, this_image(coarray)
13+
print *, this_image(coscalar,1)
14+
print *, this_image(coarray,1)
15+
16+
!ERROR: 'coarray=' argument must have corank > 0 for intrinsic 'this_image'
17+
print *, this_image(array,1)
18+
19+
! TODO: More complete testing requires implementation of team_type
20+
! actual arguments in flang/lib/Evaluate/intrinsics.cpp
21+
22+
end subroutine

0 commit comments

Comments
 (0)