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
15 I recently added a semantic check to the Flang compiler front end. This document
16 describes my thought process and the resulting implementation.
18 For more information about the compiler, start with the
19 [compiler overview](Overview.md).
23 In the 2018 Fortran standard, section 11.1.7.4.3, paragraph 2, states that:
26 Except for the incrementation of the DO variable that occurs in step (3), the DO variable
27 shall neither be redefined nor become undefined while the DO construct is active.
29 One of the ways that DO variables might be redefined is if they are passed to
30 functions with dummy arguments whose `INTENT` is `INTENT(OUT)` or
31 `INTENT(INOUT)`. I implemented this semantic check. Specifically, I changed
32 the compiler to emit an error message if an active DO variable was passed to a
33 dummy argument of a FUNCTION with INTENT(OUT). Similarly, I had the compiler
34 emit a warning if an active DO variable was passed to a dummy argument with
35 INTENT(INOUT). Previously, I had implemented similar checks for SUBROUTINE
40 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:
47 jvar = intentOutFunc(ivar) ! Error since ivar is a DO variable
51 function intentOutFunc(dummyArg)
52 integer, intent(out) :: dummyArg
53 integer :: intentOutFunc
56 end function intentOutFunc
60 I verified that other Fortran compilers produced an error message at the point
61 of the call to `intentOutFunc()`:
64 jvar = intentOutFunc(ivar) ! Error since ivar is a DO variable
68 I also used this program to produce a parse tree for the program using the command:
70 flang-new -fc1 -fdebug-dump-parse-tree testfun.f90
73 Here's the relevant fragment of the parse tree produced by the compiler:
76 | | ExecutionPartConstruct -> ExecutableConstruct -> DoConstruct
78 | | | | LoopControl -> LoopBounds
79 | | | | | Scalar -> Name = 'ivar'
80 | | | | | Scalar -> Expr = '1_4'
81 | | | | | | LiteralConstant -> IntLiteralConstant = '1'
82 | | | | | Scalar -> Expr = '10_4'
83 | | | | | | LiteralConstant -> IntLiteralConstant = '10'
85 | | | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'jvar=intentoutfunc(ivar)'
86 | | | | | Variable -> Designator -> DataRef -> Name = 'jvar'
87 | | | | | Expr = 'intentoutfunc(ivar)'
88 | | | | | | FunctionReference -> Call
89 | | | | | | | ProcedureDesignator -> Name = 'intentoutfunc'
90 | | | | | | | ActualArgSpec
91 | | | | | | | | ActualArg -> Expr = 'ivar'
92 | | | | | | | | | Designator -> DataRef -> Name = 'ivar'
96 Note that this fragment of the tree only shows four `parser::Expr` nodes,
97 but the full parse tree also contained a fifth `parser::Expr` node for the
98 constant 216 in the statement:
103 ## Analysis and implementation planning
105 I then considered what I needed to do. I needed to detect situations where an
106 active DO variable was passed to a dummy argument with `INTENT(OUT)` or
107 `INTENT(INOUT)`. Once I detected such a situation, I needed to produce a
108 message that highlighted the erroneous source code.
110 ### Deciding where to add the code to the compiler
111 This new semantic check would depend on several types of information -- the
112 parse tree, source code location information, symbols, and expressions. Thus I
113 needed to put my new code in a place in the compiler after the parse tree had
114 been created, name resolution had already happened, and expression semantic
115 checking had already taken place.
117 Most semantic checks for statements are implemented by walking the parse tree
118 and performing analysis on the nodes they visit. My plan was to use this
119 method. The infrastructure for walking the parse tree for statement semantic
120 checking is implemented in the files `lib/Semantics/semantics.cpp`.
121 Here's a fragment of the declaration of the framework's parse tree visitor from
122 `lib/Semantics/semantics.cpp`:
125 // A parse tree visitor that calls Enter/Leave functions from each checker
126 // class C supplied as template parameters. Enter is called before the node's
127 // children are visited, Leave is called after. No two checkers may have the
128 // same Enter or Leave function. Each checker must be constructible from
129 // SemanticsContext and have BaseChecker as a virtual base class.
130 template<typename... C> class SemanticsVisitor : public virtual C... {
134 using BaseChecker::Enter;
135 using BaseChecker::Leave;
136 SemanticsVisitor(SemanticsContext &context)
137 : C{context}..., context_{context} {}
142 Since FUNCTION calls are a kind of expression, I was planning to base my
143 implementation on the contents of `parser::Expr` nodes. I would need to define
144 either an `Enter()` or `Leave()` function whose parameter was a `parser::Expr`
145 node. Here's the declaration I put into `lib/Semantics/check-do.h`:
148 void Leave(const parser::Expr &);
150 The `Enter()` functions get called at the time the node is first visited --
151 that is, before its children. The `Leave()` function gets called after the
152 children are visited. For my check the visitation order didn't matter, so I
153 arbitrarily chose to implement the `Leave()` function to visit the parse tree
156 Since my semantic check was focused on DO CONCURRENT statements, I added it to
157 the file `lib/Semantics/check-do.cpp` where most of the semantic checking for
158 DO statements already lived.
160 ### Taking advantage of prior work
161 When implementing a similar check for SUBROUTINE calls, I created a utility
162 functions in `lib/Semantics/semantics.cpp` to emit messages if
163 a symbol corresponding to an active DO variable was being potentially modified:
166 void WarnDoVarRedefine(const parser::CharBlock &location, const Symbol &var);
167 void CheckDoVarRedefine(const parser::CharBlock &location, const Symbol &var);
170 The first function is intended for dummy arguments of `INTENT(INOUT)` and
171 the second for `INTENT(OUT)`.
173 Thus I needed three pieces of
175 1. the source location of the erroneous text,
176 2. the `INTENT` of the associated dummy argument, and
177 3. the relevant symbol passed as the actual argument.
179 The first and third are needed since they're required to call the utility
180 functions. The second is needed to determine whether to call them.
182 ### Finding the source location
183 The source code location information that I'd need for the error message must
184 come from the parse tree. I looked in the file
185 `include/flang/Parser/parse-tree.h` and determined that a `struct Expr`
186 contained source location information since it had the field `CharBlock
187 source`. Thus, if I visited a `parser::Expr` node, I could get the source
188 location information for the associated expression.
190 ### Determining the `INTENT`
191 I knew that I could find the `INTENT` of the dummy argument associated with the
192 actual argument from the function called `dummyIntent()` in the class
193 `evaluate::ActualArgument` in the file `include/flang/Evaluate/call.h`. So
194 if I could find an `evaluate::ActualArgument` in an expression, I could
195 determine the `INTENT` of the associated dummy argument. I knew that it was
196 valid to call `dummyIntent()` because the data on which `dummyIntent()`
197 depends is established during semantic processing for expressions, and the
198 semantic processing for expressions happens before semantic checking for DO
201 In my prior work on checking the INTENT of arguments for SUBROUTINE calls,
202 the parse tree held a node for the call (a `parser::CallStmt`) that contained
203 an `evaluate::ProcedureRef` node.
206 WRAPPER_CLASS_BOILERPLATE(CallStmt, Call);
207 mutable std::unique_ptr<evaluate::ProcedureRef,
208 common::Deleter<evaluate::ProcedureRef>>
209 typedCall; // filled by semantics
212 The `evaluate::ProcedureRef` contains a list of `evaluate::ActualArgument`
213 nodes. I could then find the INTENT of a dummy argument from the
214 `evaluate::ActualArgument` node.
216 For a FUNCTION call, though, there is no similar way to get from a parse tree
217 node to an `evaluate::ProcedureRef` node. But I knew that there was an
218 existing framework used in DO construct semantic checking that traversed an
219 `evaluate::Expr` node collecting `semantics::Symbol` nodes. I guessed that I'd
220 be able to use a similar framework to traverse an `evaluate::Expr` node to
221 find all of the `evaluate::ActualArgument` nodes.
223 Note that the compiler has multiple types called `Expr`. One is in the
224 `parser` namespace. `parser::Expr` is defined in the file
225 `include/flang/Parser/parse-tree.h`. It represents a parsed expression that
226 maps directly to the source code and has fields that specify any operators in
227 the expression, the operands, and the source position of the expression.
229 Additionally, in the namespace `evaluate`, there are `evaluate::Expr<T>`
230 template classes defined in the file `include/flang/Evaluate/expression.h`.
231 These are parameterized over the various types of Fortran and constitute a
232 suite of strongly-typed representations of valid Fortran expressions of type
233 `T` that have been fully elaborated with conversion operations and subjected to
234 constant folding. After an expression has undergone semantic analysis, the
235 field `typedExpr` in the `parser::Expr` node is filled in with a pointer that
236 owns an instance of `evaluate::Expr<SomeType>`, the most general representation
237 of an analyzed expression.
239 All of the declarations associated with both FUNCTION and SUBROUTINE calls are
240 in `include/flang/Evaluate/call.h`. An `evaluate::FunctionRef` inherits from
241 an `evaluate::ProcedureRef` which contains the list of
242 `evaluate::ActualArgument` nodes. But the relationship between an
243 `evaluate::FunctionRef` node and its associated arguments is not relevant. I
244 only needed to find the `evaluate::ActualArgument` nodes in an expression.
245 They hold all of the information I needed.
247 So my plan was to start with the `parser::Expr` node and extract its
248 associated `evaluate::Expr` field. I would then traverse the
249 `evaluate::Expr` tree collecting all of the `evaluate::ActualArgument`
250 nodes. I would look at each of these nodes to determine the `INTENT` of
251 the associated dummy argument.
253 This combination of the traversal framework and `dummyIntent()` would give
254 me the `INTENT` of all of the dummy arguments in a FUNCTION call. Thus, I
255 would have the second piece of information I needed.
257 ### Determining if the actual argument is a variable
258 I also guessed that I could determine if the `evaluate::ActualArgument`
259 consisted of a variable.
261 Once I had a symbol for the variable, I could call one of the functions:
263 void WarnDoVarRedefine(const parser::CharBlock &, const Symbol &);
264 void CheckDoVarRedefine(const parser::CharBlock &, const Symbol &);
266 to emit the messages.
268 If my plans worked out, this would give me the three pieces of information I
269 needed -- the source location of the erroneous text, the `INTENT` of the dummy
270 argument, and a symbol that I could use to determine whether the actual
271 argument was an active DO variable.
275 ### Adding a parse tree visitor
276 I started my implementation by adding a visitor for `parser::Expr` nodes.
277 Since this analysis is part of DO construct checking, I did this in
278 `lib/Semantics/check-do.cpp`. I added a print statement to the visitor to
279 verify that my new code was actually getting executed.
281 In `lib/Semantics/check-do.h`, I added the declaration for the visitor:
284 void Leave(const parser::Expr &);
287 In `lib/Semantics/check-do.cpp`, I added an (almost empty) implementation:
290 void DoChecker::Leave(const parser::Expr &) {
291 std::cout << "In Leave for parser::Expr\n";
295 I then built the compiler with these changes and ran it on my test program.
296 This time, I made sure to invoke semantic checking. Here's the command I used:
298 flang-new -fc1 -fdebug-unparse-with-symbols testfun.f90
301 This produced the output:
304 In Leave for parser::Expr
305 In Leave for parser::Expr
306 In Leave for parser::Expr
307 In Leave for parser::Expr
308 In Leave for parser::Expr
311 This made sense since the parse tree contained five `parser::Expr` nodes.
312 So far, so good. Note that a `parse::Expr` node has a field with the
313 source position of the associated expression (`CharBlock source`). So I
314 now had one of the three pieces of information needed to detect and report
317 ### Collecting the actual arguments
318 To get the `INTENT` of the dummy arguments and the `semantics::Symbol` associated with the
319 actual argument, I needed to find all of the actual arguments embedded in an
320 expression that contained a FUNCTION call. So my next step was to write the
321 framework to walk the `evaluate::Expr` to gather all of the
322 `evaluate::ActualArgument` nodes. The code that I planned to model it on
323 was the existing infrastructure that collected all of the `semantics::Symbol` nodes from an
324 `evaluate::Expr`. I found this implementation in
325 `lib/Evaluate/tools.cpp`:
328 struct CollectSymbolsHelper
329 : public SetTraverse<CollectSymbolsHelper, semantics::SymbolSet> {
330 using Base = SetTraverse<CollectSymbolsHelper, semantics::SymbolSet>;
331 CollectSymbolsHelper() : Base{*this} {}
332 using Base::operator();
333 semantics::SymbolSet operator()(const Symbol &symbol) const {
337 template<typename A> semantics::SymbolSet CollectSymbols(const A &x) {
338 return CollectSymbolsHelper{}(x);
342 Note that the `CollectSymbols()` function returns a `semantics::Symbolset`,
343 which is declared in `include/flang/Semantics/symbol.h`:
346 using SymbolSet = std::set<SymbolRef>;
349 This infrastructure yields a collection based on `std::set<>`. Using an
350 `std::set<>` means that if the same object is inserted twice, the
351 collection only gets one copy. This was the behavior that I wanted.
353 Here's a sample invocation of `CollectSymbols()` that I found:
355 if (const auto *expr{GetExpr(parsedExpr)}) {
356 for (const Symbol &symbol : evaluate::CollectSymbols(*expr)) {
359 I noted that a `SymbolSet` did not actually contain an
360 `std::set<Symbol>`. This wasn't surprising since we don't want to put the
361 full `semantics::Symbol` objects into the set. Ideally, we would be able to create an
362 `std::set<Symbol &>` (a set of C++ references to symbols). But C++ doesn't
363 support sets that contain references. This limitation is part of the rationale
364 for the Flang implementation of type `common::Reference`, which is defined in
365 `include/flang/Common/reference.h`.
367 `SymbolRef`, the specialization of the template `common::Reference` for
368 `semantics::Symbol`, is declared in the file
369 `include/flang/Semantics/symbol.h`:
372 using SymbolRef = common::Reference<const Symbol>;
375 So to implement something that would collect `evaluate::ActualArgument`
376 nodes from an `evaluate::Expr`, I first defined the required types
377 `ActualArgumentRef` and `ActualArgumentSet`. Since these are being
378 used exclusively for DO construct semantic checking (currently), I put their
379 definitions into `lib/Semantics/check-do.cpp`:
383 namespace Fortran::evaluate {
384 using ActualArgumentRef = common::Reference<const ActualArgument>;
388 using ActualArgumentSet = std::set<evaluate::ActualArgumentRef>;
391 Since `ActualArgument` is in the namespace `evaluate`, I put the
392 definition for `ActualArgumentRef` in that namespace, too.
394 I then modeled the code to create an `ActualArgumentSet` after the code to
395 collect a `SymbolSet` and put it into `lib/Semantics/check-do.cpp`:
399 struct CollectActualArgumentsHelper
400 : public evaluate::SetTraverse<CollectActualArgumentsHelper,
402 using Base = SetTraverse<CollectActualArgumentsHelper, ActualArgumentSet>;
403 CollectActualArgumentsHelper() : Base{*this} {}
404 using Base::operator();
405 ActualArgumentSet operator()(const evaluate::ActualArgument &arg) const {
406 return ActualArgumentSet{arg};
410 template<typename A> ActualArgumentSet CollectActualArguments(const A &x) {
411 return CollectActualArgumentsHelper{}(x);
414 template ActualArgumentSet CollectActualArguments(const SomeExpr &);
417 Unfortunately, when I tried to build this code, I got an error message saying
418 `std::set` requires the `<` operator to be defined for its contents.
419 To fix this, I added a definition for `<`. I didn't care how `<` was
420 defined, so I just used the address of the object:
423 inline bool operator<(ActualArgumentRef x, ActualArgumentRef y) {
428 I was surprised when this did not make the error message saying that I needed
429 the `<` operator go away. Eventually, I figured out that the definition of
430 the `<` operator needed to be in the `evaluate` namespace. Once I put
431 it there, everything compiled successfully. Here's the code that worked:
434 namespace Fortran::evaluate {
435 using ActualArgumentRef = common::Reference<const ActualArgument>;
437 inline bool operator<(ActualArgumentRef x, ActualArgumentRef y) {
443 I then modified my visitor for the parser::Expr to invoke my new collection
444 framework. To verify that it was actually doing something, I printed out the
445 number of `evaluate::ActualArgument` nodes that it collected. Note the
446 call to `GetExpr()` in the invocation of `CollectActualArguments()`. I
447 modeled this on similar code that collected a `SymbolSet` described above:
450 void DoChecker::Leave(const parser::Expr &parsedExpr) {
451 std::cout << "In Leave for parser::Expr\n";
452 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
453 std::cout << "Number of arguments: " << argSet.size() << "\n";
457 I compiled and tested this code on my little test program. Here's the output that I got:
459 In Leave for parser::Expr
460 Number of arguments: 0
461 In Leave for parser::Expr
462 Number of arguments: 0
463 In Leave for parser::Expr
464 Number of arguments: 0
465 In Leave for parser::Expr
466 Number of arguments: 1
467 In Leave for parser::Expr
468 Number of arguments: 0
471 So most of the `parser::Expr`nodes contained no actual arguments, but the
472 fourth expression in the parse tree walk contained a single argument. This may
473 seem wrong since the third `parser::Expr` node in the file contains the
474 `FunctionReference` node along with the arguments that we're gathering.
475 But since the tree walk function is being called upon leaving a
476 `parser::Expr` node, the function visits the `parser::Expr` node
477 associated with the `parser::ActualArg` node before it visits the
478 `parser::Expr` node associated with the `parser::FunctionReference`
483 ### Finding the `INTENT` of the dummy argument
484 I now wanted to find the `INTENT` of the dummy argument associated with the
485 arguments in the set. As mentioned earlier, the type
486 `evaluate::ActualArgument` has a member function called `dummyIntent()`
487 that gives this value. So I augmented my code to print out the `INTENT`:
490 void DoChecker::Leave(const parser::Expr &parsedExpr) {
491 std::cout << "In Leave for parser::Expr\n";
492 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
493 std::cout << "Number of arguments: " << argSet.size() << "\n";
494 for (const evaluate::ActualArgumentRef &argRef : argSet) {
495 common::Intent intent{argRef->dummyIntent()};
497 case common::Intent::In: std::cout << "INTENT(IN)\n"; break;
498 case common::Intent::Out: std::cout << "INTENT(OUT)\n"; break;
499 case common::Intent::InOut: std::cout << "INTENT(INOUT)\n"; break;
500 default: std::cout << "default INTENT\n";
506 I then rebuilt my compiler and ran it on my test case. This produced the following output:
509 In Leave for parser::Expr
510 Number of arguments: 0
511 In Leave for parser::Expr
512 Number of arguments: 0
513 In Leave for parser::Expr
514 Number of arguments: 0
515 In Leave for parser::Expr
516 Number of arguments: 1
518 In Leave for parser::Expr
519 Number of arguments: 0
522 I then modified my test case to convince myself that I was getting the correct
523 `INTENT` for `IN`, `INOUT`, and default cases.
527 ### Finding the symbols for arguments that are variables
528 The third and last piece of information I needed was to determine if a variable
529 was being passed as an actual argument. In such cases, I wanted to get the
530 symbol table node (`semantics::Symbol`) for the variable. My starting point was the
531 `evaluate::ActualArgument` node.
533 I was unsure of how to do this, so I browsed through existing code to look for
534 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
535 uses of `ActualArgument`. One of the first hits I got was in `lib/Evaluate/call.cpp` in the definition of `ActualArgument::GetType()`:
538 std::optional<DynamicType> ActualArgument::GetType() const {
539 if (const Expr<SomeType> *expr{UnwrapExpr()}) {
540 return expr->GetType();
541 } else if (std::holds_alternative<AssumedType>(u_)) {
542 return DynamicType::AssumedType();
549 I noted the call to `UnwrapExpr()` that yielded a value of
550 `Expr<SomeType>`. So I guessed that I could use this member function to
551 get an `evaluate::Expr<SomeType>` on which I could perform further analysis.
553 I also knew that the header file `include/flang/Evaluate/tools.h` held many
554 utility functions for dealing with `evaluate::Expr` objects. I was hoping to
555 find something that would determine if an `evaluate::Expr` was a variable. So
556 I searched for `IsVariable` and got a hit immediately.
558 template<typename A> bool IsVariable(const A &x) {
559 if (auto known{IsVariableHelper{}(x)}) {
567 But I actually needed more than just the knowledge that an `evaluate::Expr` was
568 a variable. I needed the `semantics::Symbol` associated with the variable. So
569 I searched in `include/flang/Evaluate/tools.h` for functions that returned a
570 `semantics::Symbol`. I found the following:
573 // If an expression is simply a whole symbol data designator,
574 // extract and return that symbol, else null.
575 template<typename A> const Symbol *UnwrapWholeSymbolDataRef(const A &x) {
576 if (auto dataRef{ExtractDataRef(x)}) {
577 if (const SymbolRef * p{std::get_if<SymbolRef>(&dataRef->u)}) {
585 This was exactly what I wanted. DO variables must be whole symbols. So I
586 could try to extract a whole `semantics::Symbol` from the `evaluate::Expr` in my
587 `evaluate::ActualArgument`. If this extraction resulted in a `semantics::Symbol`
588 that wasn't a `nullptr`, I could then conclude if it was a variable that I
589 could pass to existing functions that would determine if it was an active DO
592 I then modified the compiler to perform the analysis that I'd guessed would
596 void DoChecker::Leave(const parser::Expr &parsedExpr) {
597 std::cout << "In Leave for parser::Expr\n";
598 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
599 std::cout << "Number of arguments: " << argSet.size() << "\n";
600 for (const evaluate::ActualArgumentRef &argRef : argSet) {
601 if (const SomeExpr * argExpr{argRef->UnwrapExpr()}) {
602 std::cout << "Got an unwrapped Expr\n";
603 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
604 std::cout << "Found a whole variable: " << *var << "\n";
607 common::Intent intent{argRef->dummyIntent()};
609 case common::Intent::In: std::cout << "INTENT(IN)\n"; break;
610 case common::Intent::Out: std::cout << "INTENT(OUT)\n"; break;
611 case common::Intent::InOut: std::cout << "INTENT(INOUT)\n"; break;
612 default: std::cout << "default INTENT\n";
618 Note the line that prints out the symbol table entry for the variable:
621 std::cout << "Found a whole variable: " << *var << "\n";
624 The compiler defines the "<<" operator for `semantics::Symbol`, which is handy
625 for analyzing the compiler's behavior.
627 Here's the result of running the modified compiler on my Fortran test case:
630 In Leave for parser::Expr
631 Number of arguments: 0
632 In Leave for parser::Expr
633 Number of arguments: 0
634 In Leave for parser::Expr
635 Number of arguments: 0
636 In Leave for parser::Expr
637 Number of arguments: 1
638 Got an unwrapped Expr
639 Found a whole variable: ivar: ObjectEntity type: INTEGER(4)
641 In Leave for parser::Expr
642 Number of arguments: 0
647 ### Emitting the messages
648 At this point, using the source location information from the original
649 `parser::Expr`, I had enough information to plug into the exiting
650 interfaces for emitting messages for active DO variables. I modified the
651 compiler code accordingly:
655 void DoChecker::Leave(const parser::Expr &parsedExpr) {
656 std::cout << "In Leave for parser::Expr\n";
657 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
658 std::cout << "Number of arguments: " << argSet.size() << "\n";
659 for (const evaluate::ActualArgumentRef &argRef : argSet) {
660 if (const SomeExpr * argExpr{argRef->UnwrapExpr()}) {
661 std::cout << "Got an unwrapped Expr\n";
662 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
663 std::cout << "Found a whole variable: " << *var << "\n";
664 common::Intent intent{argRef->dummyIntent()};
666 case common::Intent::In: std::cout << "INTENT(IN)\n"; break;
667 case common::Intent::Out:
668 std::cout << "INTENT(OUT)\n";
669 context_.CheckDoVarRedefine(parsedExpr.source, *var);
671 case common::Intent::InOut:
672 std::cout << "INTENT(INOUT)\n";
673 context_.WarnDoVarRedefine(parsedExpr.source, *var);
675 default: std::cout << "default INTENT\n";
683 I then ran this code on my test case, and miraculously, got the following
687 In Leave for parser::Expr
688 Number of arguments: 0
689 In Leave for parser::Expr
690 Number of arguments: 0
691 In Leave for parser::Expr
692 Number of arguments: 0
693 In Leave for parser::Expr
694 Number of arguments: 1
695 Got an unwrapped Expr
696 Found a whole variable: ivar: ObjectEntity type: INTEGER(4)
698 In Leave for parser::Expr
699 Number of arguments: 0
700 testfun.f90:6:12: error: Cannot redefine DO variable 'ivar'
701 jvar = intentOutFunc(ivar)
703 testfun.f90:5:6: Enclosing DO construct
710 ## Improving the test case
711 At this point, my implementation seemed to be working. But I was concerned
712 about the limitations of my test case. So I augmented it to include arguments
713 other than `INTENT(OUT)` and more complex expressions. Luckily, my
714 augmented test did not reveal any new problems.
716 Here's the test I ended up with:
721 Integer :: ivar, jvar
725 jvar = intentInFunc(ivar)
728 ! Error for passing a DO variable to an INTENT(OUT) dummy
730 jvar = intentOutFunc(ivar)
733 ! Error for passing a DO variable to an INTENT(OUT) dummy, more complex
736 jvar = 83 + intentInFunc(intentOutFunc(ivar))
739 ! Warning for passing a DO variable to an INTENT(INOUT) dummy
741 jvar = intentInOutFunc(ivar)
745 function intentInFunc(dummyArg)
746 integer, intent(in) :: dummyArg
747 integer :: intentInFunc
750 end function intentInFunc
752 function intentOutFunc(dummyArg)
753 integer, intent(out) :: dummyArg
754 integer :: intentOutFunc
758 end function intentOutFunc
760 function intentInOutFunc(dummyArg)
761 integer, intent(inout) :: dummyArg
762 integer :: intentInOutFunc
765 intentInOutFunc = 343
766 end function intentInOutFunc
771 ## Submitting the pull request
772 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
773 to make sure that the names were clear. Here's what I ended up with:
776 void DoChecker::Leave(const parser::Expr &parsedExpr) {
777 ActualArgumentSet argSet{CollectActualArguments(GetExpr(parsedExpr))};
778 for (const evaluate::ActualArgumentRef &argRef : argSet) {
779 if (const SomeExpr * argExpr{argRef->UnwrapExpr()}) {
780 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
781 common::Intent intent{argRef->dummyIntent()};
783 case common::Intent::Out:
784 context_.CheckDoVarRedefine(parsedExpr.source, *var);
786 case common::Intent::InOut:
787 context_.WarnDoVarRedefine(parsedExpr.source, *var);
789 default:; // INTENT(IN) or default intent
797 I then created a pull request to get review comments.
799 ## Responding to pull request comments
800 I got feedback suggesting that I use an `if` statement rather than a
801 `case` statement. Another comment reminded me that I should look at the
802 code I'd previously writted to do a similar check for SUBROUTINE calls to see
803 if there was an opportunity to share code. This examination resulted in
804 converting my existing code to the following pair of functions:
808 static void CheckIfArgIsDoVar(const evaluate::ActualArgument &arg,
809 const parser::CharBlock location, SemanticsContext &context) {
810 common::Intent intent{arg.dummyIntent()};
811 if (intent == common::Intent::Out || intent == common::Intent::InOut) {
812 if (const SomeExpr * argExpr{arg.UnwrapExpr()}) {
813 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
814 if (intent == common::Intent::Out) {
815 context.CheckDoVarRedefine(location, *var);
817 context.WarnDoVarRedefine(location, *var); // INTENT(INOUT)
824 void DoChecker::Leave(const parser::Expr &parsedExpr) {
825 if (const SomeExpr * expr{GetExpr(parsedExpr)}) {
826 ActualArgumentSet argSet{CollectActualArguments(*expr)};
827 for (const evaluate::ActualArgumentRef &argRef : argSet) {
828 CheckIfArgIsDoVar(*argRef, parsedExpr.source, context_);
834 The function `CheckIfArgIsDoVar()` was shared with the checks for DO
835 variables being passed to SUBROUTINE calls.
837 At this point, my pull request was approved, and I merged it and deleted the