1 <!--===- docs/ImplementingASemanticCheck.md
3 Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 See https://llvm.org/LICENSE.txt for license information.
5 SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
8 # How to implement a Sematic Check in Flang
16 I recently added a semantic check to the Flang compiler front end. This document
17 describes my thought process and the resulting implementation.
19 For more information about the compiler, start with the
20 [compiler overview](Overview.md).
24 In the 2018 Fortran standard, section 11.1.7.4.3, paragraph 2, states that:
27 Except for the incrementation of the DO variable that occurs in step (3), the DO variable
28 shall neither be redefined nor become undefined while the DO construct is active.
30 One of the ways that DO variables might be redefined is if they are passed to
31 functions with dummy arguments whose `INTENT` is `INTENT(OUT)` or
32 `INTENT(INOUT)`. I implemented this semantic check. Specifically, I changed
33 the compiler to emit an error message if an active DO variable was passed to a
34 dummy argument of a FUNCTION with INTENT(OUT). Similarly, I had the compiler
35 emit a warning if an active DO variable was passed to a dummy argument with
36 INTENT(INOUT). Previously, I had implemented similar checks for SUBROUTINE
41 My first step was to create a test case to cause the problem. I called it testfun.f90 and used it to check the behavior of other Fortran compilers. Here's the initial version:
48 jvar = intentOutFunc(ivar) ! Error since ivar is a DO variable
52 function intentOutFunc(dummyArg)
53 integer, intent(out) :: dummyArg
54 integer :: intentOutFunc
57 end function intentOutFunc
61 I verified that other Fortran compilers produced an error message at the point
62 of the call to `intentOutFunc()`:
65 jvar = intentOutFunc(ivar) ! Error since ivar is a DO variable
69 I also used this program to produce a parse tree for the program using the command:
71 flang-new -fc1 -fdebug-dump-parse-tree testfun.f90
74 Here's the relevant fragment of the parse tree produced by the compiler:
77 | | ExecutionPartConstruct -> ExecutableConstruct -> DoConstruct
79 | | | | LoopControl -> LoopBounds
80 | | | | | Scalar -> Name = 'ivar'
81 | | | | | Scalar -> Expr = '1_4'
82 | | | | | | LiteralConstant -> IntLiteralConstant = '1'
83 | | | | | Scalar -> Expr = '10_4'
84 | | | | | | LiteralConstant -> IntLiteralConstant = '10'
86 | | | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'jvar=intentoutfunc(ivar)'
87 | | | | | Variable -> Designator -> DataRef -> Name = 'jvar'
88 | | | | | Expr = 'intentoutfunc(ivar)'
89 | | | | | | FunctionReference -> Call
90 | | | | | | | ProcedureDesignator -> Name = 'intentoutfunc'
91 | | | | | | | ActualArgSpec
92 | | | | | | | | ActualArg -> Expr = 'ivar'
93 | | | | | | | | | Designator -> DataRef -> Name = 'ivar'
97 Note that this fragment of the tree only shows four `parser::Expr` nodes,
98 but the full parse tree also contained a fifth `parser::Expr` node for the
99 constant 216 in the statement:
104 ## Analysis and implementation planning
106 I then considered what I needed to do. I needed to detect situations where an
107 active DO variable was passed to a dummy argument with `INTENT(OUT)` or
108 `INTENT(INOUT)`. Once I detected such a situation, I needed to produce a
109 message that highlighted the erroneous source code.
111 ### Deciding where to add the code to the compiler
112 This new semantic check would depend on several types of information -- the
113 parse tree, source code location information, symbols, and expressions. Thus I
114 needed to put my new code in a place in the compiler after the parse tree had
115 been created, name resolution had already happened, and expression semantic
116 checking had already taken place.
118 Most semantic checks for statements are implemented by walking the parse tree
119 and performing analysis on the nodes they visit. My plan was to use this
120 method. The infrastructure for walking the parse tree for statement semantic
121 checking is implemented in the files `lib/Semantics/semantics.cpp`.
122 Here's a fragment of the declaration of the framework's parse tree visitor from
123 `lib/Semantics/semantics.cpp`:
126 // A parse tree visitor that calls Enter/Leave functions from each checker
127 // class C supplied as template parameters. Enter is called before the node's
128 // children are visited, Leave is called after. No two checkers may have the
129 // same Enter or Leave function. Each checker must be constructible from
130 // SemanticsContext and have BaseChecker as a virtual base class.
131 template<typename... C> class SemanticsVisitor : public virtual C... {
135 using BaseChecker::Enter;
136 using BaseChecker::Leave;
137 SemanticsVisitor(SemanticsContext &context)
138 : C{context}..., context_{context} {}
143 Since FUNCTION calls are a kind of expression, I was planning to base my
144 implementation on the contents of `parser::Expr` nodes. I would need to define
145 either an `Enter()` or `Leave()` function whose parameter was a `parser::Expr`
146 node. Here's the declaration I put into `lib/Semantics/check-do.h`:
149 void Leave(const parser::Expr &);
151 The `Enter()` functions get called at the time the node is first visited --
152 that is, before its children. The `Leave()` function gets called after the
153 children are visited. For my check the visitation order didn't matter, so I
154 arbitrarily chose to implement the `Leave()` function to visit the parse tree
157 Since my semantic check was focused on DO CONCURRENT statements, I added it to
158 the file `lib/Semantics/check-do.cpp` where most of the semantic checking for
159 DO statements already lived.
161 ### Taking advantage of prior work
162 When implementing a similar check for SUBROUTINE calls, I created a utility
163 functions in `lib/Semantics/semantics.cpp` to emit messages if
164 a symbol corresponding to an active DO variable was being potentially modified:
167 void WarnDoVarRedefine(const parser::CharBlock &location, const Symbol &var);
168 void CheckDoVarRedefine(const parser::CharBlock &location, const Symbol &var);
171 The first function is intended for dummy arguments of `INTENT(INOUT)` and
172 the second for `INTENT(OUT)`.
174 Thus I needed three pieces of
176 1. the source location of the erroneous text,
177 2. the `INTENT` of the associated dummy argument, and
178 3. the relevant symbol passed as the actual argument.
180 The first and third are needed since they're required to call the utility
181 functions. The second is needed to determine whether to call them.
183 ### Finding the source location
184 The source code location information that I'd need for the error message must
185 come from the parse tree. I looked in the file
186 `include/flang/Parser/parse-tree.h` and determined that a `struct Expr`
187 contained source location information since it had the field `CharBlock
188 source`. Thus, if I visited a `parser::Expr` node, I could get the source
189 location information for the associated expression.
191 ### Determining the `INTENT`
192 I knew that I could find the `INTENT` of the dummy argument associated with the
193 actual argument from the function called `dummyIntent()` in the class
194 `evaluate::ActualArgument` in the file `include/flang/Evaluate/call.h`. So
195 if I could find an `evaluate::ActualArgument` in an expression, I could
196 determine the `INTENT` of the associated dummy argument. I knew that it was
197 valid to call `dummyIntent()` because the data on which `dummyIntent()`
198 depends is established during semantic processing for expressions, and the
199 semantic processing for expressions happens before semantic checking for DO
202 In my prior work on checking the INTENT of arguments for SUBROUTINE calls,
203 the parse tree held a node for the call (a `parser::CallStmt`) that contained
204 an `evaluate::ProcedureRef` node.
207 WRAPPER_CLASS_BOILERPLATE(CallStmt, Call);
208 mutable std::unique_ptr<evaluate::ProcedureRef,
209 common::Deleter<evaluate::ProcedureRef>>
210 typedCall; // filled by semantics
213 The `evaluate::ProcedureRef` contains a list of `evaluate::ActualArgument`
214 nodes. I could then find the INTENT of a dummy argument from the
215 `evaluate::ActualArgument` node.
217 For a FUNCTION call, though, there is no similar way to get from a parse tree
218 node to an `evaluate::ProcedureRef` node. But I knew that there was an
219 existing framework used in DO construct semantic checking that traversed an
220 `evaluate::Expr` node collecting `semantics::Symbol` nodes. I guessed that I'd
221 be able to use a similar framework to traverse an `evaluate::Expr` node to
222 find all of the `evaluate::ActualArgument` nodes.
224 Note that the compiler has multiple types called `Expr`. One is in the
225 `parser` namespace. `parser::Expr` is defined in the file
226 `include/flang/Parser/parse-tree.h`. It represents a parsed expression that
227 maps directly to the source code and has fields that specify any operators in
228 the expression, the operands, and the source position of the expression.
230 Additionally, in the namespace `evaluate`, there are `evaluate::Expr<T>`
231 template classes defined in the file `include/flang/Evaluate/expression.h`.
232 These are parameterized over the various types of Fortran and constitute a
233 suite of strongly-typed representations of valid Fortran expressions of type
234 `T` that have been fully elaborated with conversion operations and subjected to
235 constant folding. After an expression has undergone semantic analysis, the
236 field `typedExpr` in the `parser::Expr` node is filled in with a pointer that
237 owns an instance of `evaluate::Expr<SomeType>`, the most general representation
238 of an analyzed expression.
240 All of the declarations associated with both FUNCTION and SUBROUTINE calls are
241 in `include/flang/Evaluate/call.h`. An `evaluate::FunctionRef` inherits from
242 an `evaluate::ProcedureRef` which contains the list of
243 `evaluate::ActualArgument` nodes. But the relationship between an
244 `evaluate::FunctionRef` node and its associated arguments is not relevant. I
245 only needed to find the `evaluate::ActualArgument` nodes in an expression.
246 They hold all of the information I needed.
248 So my plan was to start with the `parser::Expr` node and extract its
249 associated `evaluate::Expr` field. I would then traverse the
250 `evaluate::Expr` tree collecting all of the `evaluate::ActualArgument`
251 nodes. I would look at each of these nodes to determine the `INTENT` of
252 the associated dummy argument.
254 This combination of the traversal framework and `dummyIntent()` would give
255 me the `INTENT` of all of the dummy arguments in a FUNCTION call. Thus, I
256 would have the second piece of information I needed.
258 ### Determining if the actual argument is a variable
259 I also guessed that I could determine if the `evaluate::ActualArgument`
260 consisted of a variable.
262 Once I had a symbol for the variable, I could call one of the functions:
264 void WarnDoVarRedefine(const parser::CharBlock &, const Symbol &);
265 void CheckDoVarRedefine(const parser::CharBlock &, const Symbol &);
267 to emit the messages.
269 If my plans worked out, this would give me the three pieces of information I
270 needed -- the source location of the erroneous text, the `INTENT` of the dummy
271 argument, and a symbol that I could use to determine whether the actual
272 argument was an active DO variable.
276 ### Adding a parse tree visitor
277 I started my implementation by adding a visitor for `parser::Expr` nodes.
278 Since this analysis is part of DO construct checking, I did this in
279 `lib/Semantics/check-do.cpp`. I added a print statement to the visitor to
280 verify that my new code was actually getting executed.
282 In `lib/Semantics/check-do.h`, I added the declaration for the visitor:
285 void Leave(const parser::Expr &);
288 In `lib/Semantics/check-do.cpp`, I added an (almost empty) implementation:
291 void DoChecker::Leave(const parser::Expr &) {
292 std::cout << "In Leave for parser::Expr\n";
296 I then built the compiler with these changes and ran it on my test program.
297 This time, I made sure to invoke semantic checking. Here's the command I used:
299 flang-new -fc1 -fdebug-unparse-with-symbols testfun.f90
302 This produced the output:
305 In Leave for parser::Expr
306 In Leave for parser::Expr
307 In Leave for parser::Expr
308 In Leave for parser::Expr
309 In Leave for parser::Expr
312 This made sense since the parse tree contained five `parser::Expr` nodes.
313 So far, so good. Note that a `parse::Expr` node has a field with the
314 source position of the associated expression (`CharBlock source`). So I
315 now had one of the three pieces of information needed to detect and report
318 ### Collecting the actual arguments
319 To get the `INTENT` of the dummy arguments and the `semantics::Symbol` associated with the
320 actual argument, I needed to find all of the actual arguments embedded in an
321 expression that contained a FUNCTION call. So my next step was to write the
322 framework to walk the `evaluate::Expr` to gather all of the
323 `evaluate::ActualArgument` nodes. The code that I planned to model it on
324 was the existing infrastructure that collected all of the `semantics::Symbol` nodes from an
325 `evaluate::Expr`. I found this implementation in
326 `lib/Evaluate/tools.cpp`:
329 struct CollectSymbolsHelper
330 : public SetTraverse<CollectSymbolsHelper, semantics::SymbolSet> {
331 using Base = SetTraverse<CollectSymbolsHelper, semantics::SymbolSet>;
332 CollectSymbolsHelper() : Base{*this} {}
333 using Base::operator();
334 semantics::SymbolSet operator()(const Symbol &symbol) const {
338 template<typename A> semantics::SymbolSet CollectSymbols(const A &x) {
339 return CollectSymbolsHelper{}(x);
343 Note that the `CollectSymbols()` function returns a `semantics::Symbolset`,
344 which is declared in `include/flang/Semantics/symbol.h`:
347 using SymbolSet = std::set<SymbolRef>;
350 This infrastructure yields a collection based on `std::set<>`. Using an
351 `std::set<>` means that if the same object is inserted twice, the
352 collection only gets one copy. This was the behavior that I wanted.
354 Here's a sample invocation of `CollectSymbols()` that I found:
356 if (const auto *expr{GetExpr(parsedExpr)}) {
357 for (const Symbol &symbol : evaluate::CollectSymbols(*expr)) {
360 I noted that a `SymbolSet` did not actually contain an
361 `std::set<Symbol>`. This wasn't surprising since we don't want to put the
362 full `semantics::Symbol` objects into the set. Ideally, we would be able to create an
363 `std::set<Symbol &>` (a set of C++ references to symbols). But C++ doesn't
364 support sets that contain references. This limitation is part of the rationale
365 for the Flang implementation of type `common::Reference`, which is defined in
366 `include/flang/Common/reference.h`.
368 `SymbolRef`, the specialization of the template `common::Reference` for
369 `semantics::Symbol`, is declared in the file
370 `include/flang/Semantics/symbol.h`:
373 using SymbolRef = common::Reference<const Symbol>;
376 So to implement something that would collect `evaluate::ActualArgument`
377 nodes from an `evaluate::Expr`, I first defined the required types
378 `ActualArgumentRef` and `ActualArgumentSet`. Since these are being
379 used exclusively for DO construct semantic checking (currently), I put their
380 definitions into `lib/Semantics/check-do.cpp`:
384 namespace Fortran::evaluate {
385 using ActualArgumentRef = common::Reference<const ActualArgument>;
389 using ActualArgumentSet = std::set<evaluate::ActualArgumentRef>;
392 Since `ActualArgument` is in the namespace `evaluate`, I put the
393 definition for `ActualArgumentRef` in that namespace, too.
395 I then modeled the code to create an `ActualArgumentSet` after the code to
396 collect a `SymbolSet` and put it into `lib/Semantics/check-do.cpp`:
400 struct CollectActualArgumentsHelper
401 : public evaluate::SetTraverse<CollectActualArgumentsHelper,
403 using Base = SetTraverse<CollectActualArgumentsHelper, ActualArgumentSet>;
404 CollectActualArgumentsHelper() : Base{*this} {}
405 using Base::operator();
406 ActualArgumentSet operator()(const evaluate::ActualArgument &arg) const {
407 return ActualArgumentSet{arg};
411 template<typename A> ActualArgumentSet CollectActualArguments(const A &x) {
412 return CollectActualArgumentsHelper{}(x);
415 template ActualArgumentSet CollectActualArguments(const SomeExpr &);
418 Unfortunately, when I tried to build this code, I got an error message saying
419 `std::set` requires the `<` operator to be defined for its contents.
420 To fix this, I added a definition for `<`. I didn't care how `<` was
421 defined, so I just used the address of the object:
424 inline bool operator<(ActualArgumentRef x, ActualArgumentRef y) {
429 I was surprised when this did not make the error message saying that I needed
430 the `<` operator go away. Eventually, I figured out that the definition of
431 the `<` operator needed to be in the `evaluate` namespace. Once I put
432 it there, everything compiled successfully. Here's the code that worked:
435 namespace Fortran::evaluate {
436 using ActualArgumentRef = common::Reference<const ActualArgument>;
438 inline bool operator<(ActualArgumentRef x, ActualArgumentRef y) {
444 I then modified my visitor for the parser::Expr to invoke my new collection
445 framework. To verify that it was actually doing something, I printed out the
446 number of `evaluate::ActualArgument` nodes that it collected. Note the
447 call to `GetExpr()` in the invocation of `CollectActualArguments()`. I
448 modeled this on similar code that collected a `SymbolSet` described above:
451 void DoChecker::Leave(const parser::Expr &parsedExpr) {
452 std::cout << "In Leave for parser::Expr\n";
453 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
454 std::cout << "Number of arguments: " << argSet.size() << "\n";
458 I compiled and tested this code on my little test program. Here's the output that I got:
460 In Leave for parser::Expr
461 Number of arguments: 0
462 In Leave for parser::Expr
463 Number of arguments: 0
464 In Leave for parser::Expr
465 Number of arguments: 0
466 In Leave for parser::Expr
467 Number of arguments: 1
468 In Leave for parser::Expr
469 Number of arguments: 0
472 So most of the `parser::Expr`nodes contained no actual arguments, but the
473 fourth expression in the parse tree walk contained a single argument. This may
474 seem wrong since the third `parser::Expr` node in the file contains the
475 `FunctionReference` node along with the arguments that we're gathering.
476 But since the tree walk function is being called upon leaving a
477 `parser::Expr` node, the function visits the `parser::Expr` node
478 associated with the `parser::ActualArg` node before it visits the
479 `parser::Expr` node associated with the `parser::FunctionReference`
484 ### Finding the `INTENT` of the dummy argument
485 I now wanted to find the `INTENT` of the dummy argument associated with the
486 arguments in the set. As mentioned earlier, the type
487 `evaluate::ActualArgument` has a member function called `dummyIntent()`
488 that gives this value. So I augmented my code to print out the `INTENT`:
491 void DoChecker::Leave(const parser::Expr &parsedExpr) {
492 std::cout << "In Leave for parser::Expr\n";
493 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
494 std::cout << "Number of arguments: " << argSet.size() << "\n";
495 for (const evaluate::ActualArgumentRef &argRef : argSet) {
496 common::Intent intent{argRef->dummyIntent()};
498 case common::Intent::In: std::cout << "INTENT(IN)\n"; break;
499 case common::Intent::Out: std::cout << "INTENT(OUT)\n"; break;
500 case common::Intent::InOut: std::cout << "INTENT(INOUT)\n"; break;
501 default: std::cout << "default INTENT\n";
507 I then rebuilt my compiler and ran it on my test case. This produced the following output:
510 In Leave for parser::Expr
511 Number of arguments: 0
512 In Leave for parser::Expr
513 Number of arguments: 0
514 In Leave for parser::Expr
515 Number of arguments: 0
516 In Leave for parser::Expr
517 Number of arguments: 1
519 In Leave for parser::Expr
520 Number of arguments: 0
523 I then modified my test case to convince myself that I was getting the correct
524 `INTENT` for `IN`, `INOUT`, and default cases.
528 ### Finding the symbols for arguments that are variables
529 The third and last piece of information I needed was to determine if a variable
530 was being passed as an actual argument. In such cases, I wanted to get the
531 symbol table node (`semantics::Symbol`) for the variable. My starting point was the
532 `evaluate::ActualArgument` node.
534 I was unsure of how to do this, so I browsed through existing code to look for
535 how it treated `evaluate::ActualArgument` objects. Since most of the code that deals with the `evaluate` namespace is in the lib/Evaluate directory, I looked there. I ran `grep` on all of the `.cpp` files looking for
536 uses of `ActualArgument`. One of the first hits I got was in `lib/Evaluate/call.cpp` in the definition of `ActualArgument::GetType()`:
539 std::optional<DynamicType> ActualArgument::GetType() const {
540 if (const Expr<SomeType> *expr{UnwrapExpr()}) {
541 return expr->GetType();
542 } else if (std::holds_alternative<AssumedType>(u_)) {
543 return DynamicType::AssumedType();
550 I noted the call to `UnwrapExpr()` that yielded a value of
551 `Expr<SomeType>`. So I guessed that I could use this member function to
552 get an `evaluate::Expr<SomeType>` on which I could perform further analysis.
554 I also knew that the header file `include/flang/Evaluate/tools.h` held many
555 utility functions for dealing with `evaluate::Expr` objects. I was hoping to
556 find something that would determine if an `evaluate::Expr` was a variable. So
557 I searched for `IsVariable` and got a hit immediately.
559 template<typename A> bool IsVariable(const A &x) {
560 if (auto known{IsVariableHelper{}(x)}) {
568 But I actually needed more than just the knowledge that an `evaluate::Expr` was
569 a variable. I needed the `semantics::Symbol` associated with the variable. So
570 I searched in `include/flang/Evaluate/tools.h` for functions that returned a
571 `semantics::Symbol`. I found the following:
574 // If an expression is simply a whole symbol data designator,
575 // extract and return that symbol, else null.
576 template<typename A> const Symbol *UnwrapWholeSymbolDataRef(const A &x) {
577 if (auto dataRef{ExtractDataRef(x)}) {
578 if (const SymbolRef * p{std::get_if<SymbolRef>(&dataRef->u)}) {
586 This was exactly what I wanted. DO variables must be whole symbols. So I
587 could try to extract a whole `semantics::Symbol` from the `evaluate::Expr` in my
588 `evaluate::ActualArgument`. If this extraction resulted in a `semantics::Symbol`
589 that wasn't a `nullptr`, I could then conclude if it was a variable that I
590 could pass to existing functions that would determine if it was an active DO
593 I then modified the compiler to perform the analysis that I'd guessed would
597 void DoChecker::Leave(const parser::Expr &parsedExpr) {
598 std::cout << "In Leave for parser::Expr\n";
599 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
600 std::cout << "Number of arguments: " << argSet.size() << "\n";
601 for (const evaluate::ActualArgumentRef &argRef : argSet) {
602 if (const SomeExpr * argExpr{argRef->UnwrapExpr()}) {
603 std::cout << "Got an unwrapped Expr\n";
604 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
605 std::cout << "Found a whole variable: " << *var << "\n";
608 common::Intent intent{argRef->dummyIntent()};
610 case common::Intent::In: std::cout << "INTENT(IN)\n"; break;
611 case common::Intent::Out: std::cout << "INTENT(OUT)\n"; break;
612 case common::Intent::InOut: std::cout << "INTENT(INOUT)\n"; break;
613 default: std::cout << "default INTENT\n";
619 Note the line that prints out the symbol table entry for the variable:
622 std::cout << "Found a whole variable: " << *var << "\n";
625 The compiler defines the "<<" operator for `semantics::Symbol`, which is handy
626 for analyzing the compiler's behavior.
628 Here's the result of running the modified compiler on my Fortran test case:
631 In Leave for parser::Expr
632 Number of arguments: 0
633 In Leave for parser::Expr
634 Number of arguments: 0
635 In Leave for parser::Expr
636 Number of arguments: 0
637 In Leave for parser::Expr
638 Number of arguments: 1
639 Got an unwrapped Expr
640 Found a whole variable: ivar: ObjectEntity type: INTEGER(4)
642 In Leave for parser::Expr
643 Number of arguments: 0
648 ### Emitting the messages
649 At this point, using the source location information from the original
650 `parser::Expr`, I had enough information to plug into the exiting
651 interfaces for emitting messages for active DO variables. I modified the
652 compiler code accordingly:
656 void DoChecker::Leave(const parser::Expr &parsedExpr) {
657 std::cout << "In Leave for parser::Expr\n";
658 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
659 std::cout << "Number of arguments: " << argSet.size() << "\n";
660 for (const evaluate::ActualArgumentRef &argRef : argSet) {
661 if (const SomeExpr * argExpr{argRef->UnwrapExpr()}) {
662 std::cout << "Got an unwrapped Expr\n";
663 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
664 std::cout << "Found a whole variable: " << *var << "\n";
665 common::Intent intent{argRef->dummyIntent()};
667 case common::Intent::In: std::cout << "INTENT(IN)\n"; break;
668 case common::Intent::Out:
669 std::cout << "INTENT(OUT)\n";
670 context_.CheckDoVarRedefine(parsedExpr.source, *var);
672 case common::Intent::InOut:
673 std::cout << "INTENT(INOUT)\n";
674 context_.WarnDoVarRedefine(parsedExpr.source, *var);
676 default: std::cout << "default INTENT\n";
684 I then ran this code on my test case, and miraculously, got the following
688 In Leave for parser::Expr
689 Number of arguments: 0
690 In Leave for parser::Expr
691 Number of arguments: 0
692 In Leave for parser::Expr
693 Number of arguments: 0
694 In Leave for parser::Expr
695 Number of arguments: 1
696 Got an unwrapped Expr
697 Found a whole variable: ivar: ObjectEntity type: INTEGER(4)
699 In Leave for parser::Expr
700 Number of arguments: 0
701 testfun.f90:6:12: error: Cannot redefine DO variable 'ivar'
702 jvar = intentOutFunc(ivar)
704 testfun.f90:5:6: Enclosing DO construct
711 ## Improving the test case
712 At this point, my implementation seemed to be working. But I was concerned
713 about the limitations of my test case. So I augmented it to include arguments
714 other than `INTENT(OUT)` and more complex expressions. Luckily, my
715 augmented test did not reveal any new problems.
717 Here's the test I ended up with:
722 Integer :: ivar, jvar
726 jvar = intentInFunc(ivar)
729 ! Error for passing a DO variable to an INTENT(OUT) dummy
731 jvar = intentOutFunc(ivar)
734 ! Error for passing a DO variable to an INTENT(OUT) dummy, more complex
737 jvar = 83 + intentInFunc(intentOutFunc(ivar))
740 ! Warning for passing a DO variable to an INTENT(INOUT) dummy
742 jvar = intentInOutFunc(ivar)
746 function intentInFunc(dummyArg)
747 integer, intent(in) :: dummyArg
748 integer :: intentInFunc
751 end function intentInFunc
753 function intentOutFunc(dummyArg)
754 integer, intent(out) :: dummyArg
755 integer :: intentOutFunc
759 end function intentOutFunc
761 function intentInOutFunc(dummyArg)
762 integer, intent(inout) :: dummyArg
763 integer :: intentInOutFunc
766 intentInOutFunc = 343
767 end function intentInOutFunc
772 ## Submitting the pull request
773 At this point, my implementation seemed functionally complete, so I stripped out all of the debug statements, ran `clang-format` on it and reviewed it
774 to make sure that the names were clear. Here's what I ended up with:
777 void DoChecker::Leave(const parser::Expr &parsedExpr) {
778 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
779 for (const evaluate::ActualArgumentRef &argRef : argSet) {
780 if (const SomeExpr * argExpr{argRef->UnwrapExpr()}) {
781 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
782 common::Intent intent{argRef->dummyIntent()};
784 case common::Intent::Out:
785 context_.CheckDoVarRedefine(parsedExpr.source, *var);
787 case common::Intent::InOut:
788 context_.WarnDoVarRedefine(parsedExpr.source, *var);
790 default:; // INTENT(IN) or default intent
798 I then created a pull request to get review comments.
800 ## Responding to pull request comments
801 I got feedback suggesting that I use an `if` statement rather than a
802 `case` statement. Another comment reminded me that I should look at the
803 code I'd previously writted to do a similar check for SUBROUTINE calls to see
804 if there was an opportunity to share code. This examination resulted in
805 converting my existing code to the following pair of functions:
809 static void CheckIfArgIsDoVar(const evaluate::ActualArgument &arg,
810 const parser::CharBlock location, SemanticsContext &context) {
811 common::Intent intent{arg.dummyIntent()};
812 if (intent == common::Intent::Out || intent == common::Intent::InOut) {
813 if (const SomeExpr * argExpr{arg.UnwrapExpr()}) {
814 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
815 if (intent == common::Intent::Out) {
816 context.CheckDoVarRedefine(location, *var);
818 context.WarnDoVarRedefine(location, *var); // INTENT(INOUT)
825 void DoChecker::Leave(const parser::Expr &parsedExpr) {
826 if (const SomeExpr * expr{GetExpr(parsedExpr)}) {
827 ActualArgumentSet argSet{CollectActualArguments(*expr)};
828 for (const evaluate::ActualArgumentRef &argRef : argSet) {
829 CheckIfArgIsDoVar(*argRef, parsedExpr.source, context_);
835 The function `CheckIfArgIsDoVar()` was shared with the checks for DO
836 variables being passed to SUBROUTINE calls.
838 At this point, my pull request was approved, and I merged it and deleted the