[llvm-branch-commits] [flang] 9a883bf - [flang] Clean up TODO comments and fix one (DATA constant ambiguity)

peter klausler via llvm-branch-commits llvm-branch-commits at lists.llvm.org
Tue Dec 15 13:40:20 PST 2020


Author: peter klausler
Date: 2020-12-15T13:36:07-08:00
New Revision: 9a883bfa11dd77cf2d45a25c5efc364e256e6d9a

URL: https://github.com/llvm/llvm-project/commit/9a883bfa11dd77cf2d45a25c5efc364e256e6d9a
DIFF: https://github.com/llvm/llvm-project/commit/9a883bfa11dd77cf2d45a25c5efc364e256e6d9a.diff

LOG: [flang] Clean up TODO comments and fix one (DATA constant ambiguity)

Remove resolved & moot TODO comments in Common/, Parser/,
and Evaluate/.  Address a pending one relating to parsing
ambiguity in DATA statement constants, handling it with
symbol table information in Semantics and adding a test.

Differential Revision: https://reviews.llvm.org/D93323

Added: 
    flang/test/Semantics/data10.f90

Modified: 
    flang/include/flang/Evaluate/real.h
    flang/include/flang/Parser/dump-parse-tree.h
    flang/include/flang/Parser/parse-state.h
    flang/include/flang/Parser/parse-tree.h
    flang/lib/Evaluate/check-expression.cpp
    flang/lib/Evaluate/type.cpp
    flang/lib/Parser/Fortran-parsers.cpp
    flang/lib/Parser/program-parsers.cpp
    flang/lib/Semantics/data-to-inits.cpp
    flang/lib/Semantics/rewrite-parse-tree.cpp
    flang/test/Semantics/data01.f90
    flang/test/Semantics/data06.f90

Removed: 
    


################################################################################
diff  --git a/flang/include/flang/Evaluate/real.h b/flang/include/flang/Evaluate/real.h
index 8ceb4639aa93..5864bdd7bd3a 100644
--- a/flang/include/flang/Evaluate/real.h
+++ b/flang/include/flang/Evaluate/real.h
@@ -63,10 +63,6 @@ class Real : public common::RealDetails<PREC> {
     return word_ == that.word_;
   }
 
-  // TODO: DIM, MAX, MIN, DPROD, FRACTION,
-  // INT/NINT, NEAREST, OUT_OF_RANGE,
-  // RRSPACING/SPACING, SCALE, SET_EXPONENT
-
   constexpr bool IsSignBitSet() const { return word_.BTEST(bits - 1); }
   constexpr bool IsNegative() const {
     return !IsNotANumber() && IsSignBitSet();
@@ -118,7 +114,7 @@ class Real : public common::RealDetails<PREC> {
       const Real &, Rounding rounding = defaultRounding) const;
 
   // SQRT(x**2 + y**2) but computed so as to avoid spurious overflow
-  // TODO: needed for CABS
+  // TODO: not yet implemented; needed for CABS
   ValueWithRealFlags<Real> HYPOT(
       const Real &, Rounding rounding = defaultRounding) const;
 

diff  --git a/flang/include/flang/Parser/dump-parse-tree.h b/flang/include/flang/Parser/dump-parse-tree.h
index 0d819f861495..8a7d1d1302b2 100644
--- a/flang/include/flang/Parser/dump-parse-tree.h
+++ b/flang/include/flang/Parser/dump-parse-tree.h
@@ -200,7 +200,6 @@ class ParseTreeDumper {
   NODE_ENUM(ConnectSpec::CharExpr, Kind)
   NODE(ConnectSpec, Newunit)
   NODE(ConnectSpec, Recl)
-  NODE(parser, ConstantValue)
   NODE(parser, ContainsStmt)
   NODE(parser, Contiguous)
   NODE(parser, ContiguousStmt)

diff  --git a/flang/include/flang/Parser/parse-state.h b/flang/include/flang/Parser/parse-state.h
index 00291bac4dbb..76cbb3470dc0 100644
--- a/flang/include/flang/Parser/parse-state.h
+++ b/flang/include/flang/Parser/parse-state.h
@@ -34,7 +34,6 @@ using common::LanguageFeature;
 
 class ParseState {
 public:
-  // TODO: Add a constructor for parsing a normalized module file.
   ParseState(const CookedSource &cooked)
       : p_{cooked.AsCharBlock().begin()}, limit_{cooked.AsCharBlock().end()} {}
   ParseState(const ParseState &that)

diff  --git a/flang/include/flang/Parser/parse-tree.h b/flang/include/flang/Parser/parse-tree.h
index 27998c308cc0..a2beac4737f6 100644
--- a/flang/include/flang/Parser/parse-tree.h
+++ b/flang/include/flang/Parser/parse-tree.h
@@ -426,8 +426,9 @@ struct DeclarationConstruct {
 
 // R504 specification-part -> [use-stmt]... [import-stmt]... [implicit-part]
 //                            [declaration-construct]...
-// TODO: transfer any statements after the last IMPLICIT (if any)
-// from the implicit part to the declaration constructs
+// PARAMETER, FORMAT, and ENTRY statements that appear before any other
+// kind of declaration-construct will be parsed into the implicit-part,
+// even if there are no IMPLICIT statements.
 struct SpecificationPart {
   TUPLE_CLASS_BOILERPLATE(SpecificationPart);
   std::tuple<std::list<OpenACCDeclarativeConstruct>,
@@ -861,13 +862,6 @@ struct LiteralConstant {
       u;
 };
 
-// R604 constant ->  literal-constant | named-constant
-// Renamed to dodge a clash with Constant<> template class.
-struct ConstantValue {
-  UNION_CLASS_BOILERPLATE(ConstantValue);
-  std::variant<LiteralConstant, NamedConstant> u;
-};
-
 // R807 access-spec -> PUBLIC | PRIVATE
 struct AccessSpec {
   ENUM_CLASS(Kind, Public, Private)
@@ -1412,14 +1406,15 @@ using TypedExpr = common::ForwardOwningPointer<evaluate::GenericExprWrapper>;
 //        signed-int-literal-constant | signed-real-literal-constant |
 //        null-init | initial-data-target |
 //        structure-constructor
+// N.B. Parsing ambiguities abound here without recourse to symbols
+// (see comments on R845's parser).
 struct DataStmtConstant {
   UNION_CLASS_BOILERPLATE(DataStmtConstant);
   CharBlock source;
   mutable TypedExpr typedExpr;
-  std::variant<Scalar<ConstantValue>, Scalar<ConstantSubobject>,
-      SignedIntLiteralConstant, SignedRealLiteralConstant,
-      SignedComplexLiteralConstant, NullInit, InitialDataTarget,
-      StructureConstructor>
+  std::variant<LiteralConstant, SignedIntLiteralConstant,
+      SignedRealLiteralConstant, SignedComplexLiteralConstant, NullInit,
+      common::Indirection<Designator>, StructureConstructor>
       u;
 };
 
@@ -2100,11 +2095,11 @@ WRAPPER_CLASS(EndBlockStmt, std::optional<Name>);
 // R1109 block-specification-part ->
 //         [use-stmt]... [import-stmt]...
 //         [[declaration-construct]... specification-construct]
-WRAPPER_CLASS(BlockSpecificationPart, SpecificationPart);
-// TODO: Because BlockSpecificationPart just wraps the more general
+// N.B. Because BlockSpecificationPart just wraps the more general
 // SpecificationPart, it can misrecognize an ImplicitPart as part of
 // the BlockSpecificationPart during parsing, and we have to detect and
 // flag such usage in semantics.
+WRAPPER_CLASS(BlockSpecificationPart, SpecificationPart);
 
 // R1107 block-construct ->
 //         block-stmt [block-specification-part] block end-block-stmt
@@ -2227,8 +2222,9 @@ WRAPPER_CLASS(EndDoStmt, std::optional<Name>);
 
 // R1119 do-construct -> do-stmt block end-do
 // R1120 do-stmt -> nonlabel-do-stmt | label-do-stmt
-// TODO: deprecated: DO loop ending on statement types other than END DO and
-// CONTINUE; multiple "label DO" loops ending on the same label
+// Deprecated, but supported: "label DO" loops ending on statements other
+// than END DO and CONTINUE, and multiple "label DO" loops ending on the
+// same label.
 struct DoConstruct {
   TUPLE_CLASS_BOILERPLATE(DoConstruct);
   const std::optional<LoopControl> &GetLoopControl() const;

diff  --git a/flang/lib/Evaluate/check-expression.cpp b/flang/lib/Evaluate/check-expression.cpp
index 6714588b9b6e..3e1a76232e06 100644
--- a/flang/lib/Evaluate/check-expression.cpp
+++ b/flang/lib/Evaluate/check-expression.cpp
@@ -411,8 +411,6 @@ class CheckSpecificationExprHelper
       }
     } else if (const auto *object{
                    ultimate.detailsIf<semantics::ObjectEntityDetails>()}) {
-      // TODO: what about EQUIVALENCE with data in COMMON?
-      // TODO: does this work for blank COMMON?
       if (object->commonBlock()) {
         return std::nullopt;
       }

diff  --git a/flang/lib/Evaluate/type.cpp b/flang/lib/Evaluate/type.cpp
index aa9db16b1e50..ef43edee075c 100644
--- a/flang/lib/Evaluate/type.cpp
+++ b/flang/lib/Evaluate/type.cpp
@@ -37,7 +37,6 @@ static bool IsDescriptor(const ObjectEntityDetails &details) {
   if (IsDescriptor(details.type())) {
     return true;
   }
-  // TODO: Automatic (adjustable) arrays - are they descriptors?
   for (const ShapeSpec &shapeSpec : details.shape()) {
     const auto &lb{shapeSpec.lbound().GetExplicit()};
     const auto &ub{shapeSpec.ubound().GetExplicit()};

diff  --git a/flang/lib/Parser/Fortran-parsers.cpp b/flang/lib/Parser/Fortran-parsers.cpp
index d1e2edcdae87..a21acd04ad36 100644
--- a/flang/lib/Parser/Fortran-parsers.cpp
+++ b/flang/lib/Parser/Fortran-parsers.cpp
@@ -47,13 +47,6 @@ constexpr auto nonDigitIdChar{letter || otherIdChar};
 constexpr auto rawName{nonDigitIdChar >> many(nonDigitIdChar || digit)};
 TYPE_PARSER(space >> sourced(rawName >> construct<Name>()))
 
-// R604 constant ->  literal-constant | named-constant
-// Used only via R607 int-constant and R845 data-stmt-constant.
-// The look-ahead check prevents occlusion of constant-subobject in
-// data-stmt-constant.
-TYPE_PARSER(construct<ConstantValue>(literalConstant) ||
-    construct<ConstantValue>(namedConstant / !"%"_tok / !"("_tok))
-
 // R608 intrinsic-operator ->
 //        power-op | mult-op | add-op | concat-op | rel-op |
 //        not-op | and-op | or-op | equiv-op
@@ -103,9 +96,9 @@ TYPE_PARSER(construct<DefinedOperator>(intrinsicOperator) ||
     construct<DefinedOperator>(definedOpName))
 
 // R505 implicit-part -> [implicit-part-stmt]... implicit-stmt
-// TODO: Can overshoot; any trailing PARAMETER, FORMAT, & ENTRY
-// statements after the last IMPLICIT should be transferred to the
-// list of declaration-constructs.
+// N.B. PARAMETER, FORMAT, & ENTRY statements that appear before any
+// other kind of declaration-construct will be parsed into the
+// implicit-part.
 TYPE_CONTEXT_PARSER("implicit part"_en_US,
     construct<ImplicitPart>(many(Parser<ImplicitPartStmt>{})))
 
@@ -828,21 +821,21 @@ TYPE_PARSER(construct<DataStmtRepeat>(intLiteralConstant) ||
 //        signed-int-literal-constant | signed-real-literal-constant |
 //        null-init | initial-data-target |
 //        constant-structure-constructor
-// null-init and a structure-constructor without parameters or components
-// are syntactically ambiguous in DATA, so "x()" is misparsed into a
-// null-init then fixed up later in expression semantics.
-// TODO: Some structure constructors can be misrecognized as array
-// references into constant subobjects.
-TYPE_PARSER(sourced(first(
-    construct<DataStmtConstant>(scalar(Parser<ConstantValue>{})),
-    construct<DataStmtConstant>(nullInit),
-    construct<DataStmtConstant>(scalar(constantSubobject)) / !"("_tok,
-    construct<DataStmtConstant>(Parser<StructureConstructor>{}),
+// N.B. scalar-constant and scalar-constant-subobject are ambiguous with
+// initial-data-target; null-init and structure-constructor are ambiguous
+// in the absence of parameters and components; structure-constructor with
+// components can be ambiguous with a scalar-constant-subobject.
+// So we parse literal constants, designator, null-init, and
+// structure-constructor, so that semantics can figure things out later
+// with the symbol table.
+TYPE_PARSER(sourced(first(construct<DataStmtConstant>(literalConstant),
     construct<DataStmtConstant>(signedRealLiteralConstant),
     construct<DataStmtConstant>(signedIntLiteralConstant),
     extension<LanguageFeature::SignedComplexLiteral>(
         construct<DataStmtConstant>(Parser<SignedComplexLiteralConstant>{})),
-    construct<DataStmtConstant>(initialDataTarget))))
+    construct<DataStmtConstant>(nullInit),
+    construct<DataStmtConstant>(indirect(designator) / !"("_tok),
+    construct<DataStmtConstant>(Parser<StructureConstructor>{}))))
 
 // R848 dimension-stmt ->
 //        DIMENSION [::] array-name ( array-spec )
@@ -1067,6 +1060,7 @@ TYPE_PARSER(construct<PartRef>(name,
     maybe(Parser<ImageSelector>{})))
 
 // R913 structure-component -> data-ref
+// The final part-ref in the data-ref is not allowed to have subscripts.
 TYPE_PARSER(construct<StructureComponent>(
     construct<DataRef>(some(Parser<PartRef>{} / percentOrDot)), name))
 
@@ -1125,8 +1119,6 @@ TYPE_PARSER(construct<StatVariable>(scalar(integer(variable))))
 // R932 allocation ->
 //        allocate-object [( allocate-shape-spec-list )]
 //        [lbracket allocate-coarray-spec rbracket]
-// TODO: allocate-shape-spec-list might be misrecognized as
-// the final list of subscripts in allocate-object.
 TYPE_PARSER(construct<Allocation>(Parser<AllocateObject>{},
     defaulted(parenthesized(nonemptyList(Parser<AllocateShapeSpec>{}))),
     maybe(bracketed(Parser<AllocateCoarraySpec>{}))))

diff  --git a/flang/lib/Parser/program-parsers.cpp b/flang/lib/Parser/program-parsers.cpp
index dee359e240cf..6a2208484ab2 100644
--- a/flang/lib/Parser/program-parsers.cpp
+++ b/flang/lib/Parser/program-parsers.cpp
@@ -269,9 +269,9 @@ TYPE_PARSER(construct<Rename>("OPERATOR (" >>
 
 // R1412 only -> generic-spec | only-use-name | rename
 // R1413 only-use-name -> use-name
+// N.B. generic-spec and only-use-name are ambiguous; resolved with symbols
 TYPE_PARSER(construct<Only>(Parser<Rename>{}) ||
-    construct<Only>(indirect(genericSpec)) ||
-    construct<Only>(name)) // TODO: ambiguous, accepted by genericSpec
+    construct<Only>(indirect(genericSpec)) || construct<Only>(name))
 
 // R1416 submodule ->
 //         submodule-stmt [specification-part] [module-subprogram-part]

diff  --git a/flang/lib/Semantics/data-to-inits.cpp b/flang/lib/Semantics/data-to-inits.cpp
index 381a0b17f2d7..2ef9132785e7 100644
--- a/flang/lib/Semantics/data-to-inits.cpp
+++ b/flang/lib/Semantics/data-to-inits.cpp
@@ -329,7 +329,14 @@ bool DataInitializationCompiler::InitElement(
     exprAnalyzer_.Say("Initializer for '%s' must not be a procedure"_err_en_US,
         DescribeElement());
   } else if (auto designatorType{designator.GetType()}) {
-    if (auto converted{ConvertElement(*expr, *designatorType)}) {
+    if (expr->Rank() > 0) {
+      // Because initial-data-target is ambiguous with scalar-constant and
+      // scalar-constant-subobject at parse time, enforcement of scalar-*
+      // must be deferred to here.
+      exprAnalyzer_.Say(
+          "DATA statement value initializes '%s' with an array"_err_en_US,
+          DescribeElement());
+    } else if (auto converted{ConvertElement(*expr, *designatorType)}) {
       // value non-pointer initialization
       if (std::holds_alternative<evaluate::BOZLiteralConstant>(expr->u) &&
           designatorType->category() != TypeCategory::Integer) { // 8.6.7(11)

diff  --git a/flang/lib/Semantics/rewrite-parse-tree.cpp b/flang/lib/Semantics/rewrite-parse-tree.cpp
index 2b926474cf57..071a668de7fd 100644
--- a/flang/lib/Semantics/rewrite-parse-tree.cpp
+++ b/flang/lib/Semantics/rewrite-parse-tree.cpp
@@ -43,7 +43,6 @@ class RewriteMutator {
   void Post(parser::IoUnit &);
   void Post(parser::ReadStmt &);
   void Post(parser::WriteStmt &);
-  void Post(parser::DataStmtConstant &);
 
   // Name resolution yet implemented:
   // TODO: Can some/all of these now be enabled?
@@ -176,19 +175,6 @@ void RewriteMutator::Post(parser::WriteStmt &x) {
   FixMisparsedUntaggedNamelistName(x);
 }
 
-void RewriteMutator::Post(parser::DataStmtConstant &x) {
-  if (auto *scalar{std::get_if<parser::Scalar<parser::ConstantValue>>(&x.u)}) {
-    if (auto *named{std::get_if<parser::NamedConstant>(&scalar->thing.u)}) {
-      if (const Symbol * symbol{named->v.symbol}) {
-        if (!IsNamedConstant(*symbol) && symbol->attrs().test(Attr::TARGET)) {
-          x.u = parser::InitialDataTarget{
-              parser::Designator{parser::DataRef{parser::Name{named->v}}}};
-        }
-      }
-    }
-  }
-}
-
 bool RewriteParseTree(SemanticsContext &context, parser::Program &program) {
   RewriteMutator mutator{context};
   parser::Walk(program, mutator);

diff  --git a/flang/test/Semantics/data01.f90 b/flang/test/Semantics/data01.f90
index aea40f0c78ba..84872d3cee20 100644
--- a/flang/test/Semantics/data01.f90
+++ b/flang/test/Semantics/data01.f90
@@ -59,8 +59,8 @@ subroutine CheckValue
   !OK: constant array element
   data x / a(1) /
   !C886, C887
-  !ERROR: Must be a constant value
+  !ERROR: DATA statement value 'a(int(i,kind=8))' for 'y' is not a constant
   data y / a(i) /
-  !ERROR: Must be a constant value
+  !ERROR: DATA statement value 'b(1_8)' for 'z' is not a constant
   data z / b(1) /
 end

diff  --git a/flang/test/Semantics/data06.f90 b/flang/test/Semantics/data06.f90
index 4743eff3b8b6..898606aab367 100644
--- a/flang/test/Semantics/data06.f90
+++ b/flang/test/Semantics/data06.f90
@@ -45,6 +45,6 @@ real function rfunc(x)
   data jx/t1()/
   !ERROR: DATA statement value could not be converted to the type 'INTEGER(4)' of the object 'jx'
   data jx/.false./
-  !ERROR: must be a constant
+  !ERROR: DATA statement value 'jy' for 'jx' is not a constant
   data jx/jy/
 end subroutine

diff  --git a/flang/test/Semantics/data10.f90 b/flang/test/Semantics/data10.f90
new file mode 100644
index 000000000000..244f99504567
--- /dev/null
+++ b/flang/test/Semantics/data10.f90
@@ -0,0 +1,14 @@
+! RUN: %S/test_errors.sh %s %t %f18
+type :: t
+  integer :: n
+end type
+type(t) :: x
+real, target, save :: a(1)
+real, parameter :: arrparm(1) = [3.14159]
+real, pointer :: p
+real :: y
+data x/t(1)/
+data p/a(1)/
+!ERROR: DATA statement value initializes 'y' with an array
+data y/arrparm/
+end


        


More information about the llvm-branch-commits mailing list