1<!--===- docs/ImplementingASemanticCheck.md
2
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
6
7-->
8# How to implement a Sematic Check in Flang
9
10```eval_rst
11.. contents::
12   :local:
13```
14
15I recently added a semantic check to the f18 compiler front end.  This document
16describes my thought process and the resulting implementation.
17
18For more information about the compiler, start with the
19[compiler overview](Overview.md).
20
21## Problem definition
22
23In the 2018 Fortran standard, section 11.1.7.4.3, paragraph 2, states that:
24
25```
26Except for the incrementation of the DO variable that occurs in step (3), the DO variable
27shall neither be redefined nor become undefined while the DO construct is active.
28```
29One of the ways that DO variables might be redefined is if they are passed to
30functions with dummy arguments whose `INTENT` is `INTENT(OUT)` or
31`INTENT(INOUT)`.  I implemented this semantic check.  Specifically, I changed
32the compiler to emit an error message if an active DO variable was passed to a
33dummy argument of a FUNCTION with INTENT(OUT).  Similarly, I had the compiler
34emit a warning if an active DO variable was passed to a dummy argument with
35INTENT(INOUT).  Previously, I had implemented similar checks for SUBROUTINE
36calls.
37
38## Creating a test
39
40My 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:
41
42```fortran
43  subroutine s()
44    Integer :: ivar, jvar
45
46    do ivar = 1, 10
47      jvar = intentOutFunc(ivar) ! Error since ivar is a DO variable
48    end do
49
50  contains
51    function intentOutFunc(dummyArg)
52      integer, intent(out) :: dummyArg
53      integer  :: intentOutFunc
54
55      dummyArg = 216
56    end function intentOutFunc
57  end subroutine s
58```
59
60I verified that other Fortran compilers produced an error message at the point
61of the call to `intentOutFunc()`:
62
63```fortran
64      jvar = intentOutFunc(ivar) ! Error since ivar is a DO variable
65```
66
67
68I also used this program to produce a parse tree for the program using the command:
69```bash
70  f18 -fdebug-dump-parse-tree -fparse-only testfun.f90
71```
72
73Here's the relevant fragment of the parse tree produced by the compiler:
74
75```
76| | ExecutionPartConstruct -> ExecutableConstruct -> DoConstruct
77| | | NonLabelDoStmt
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'
84| | | Block
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'
93| | | EndDoStmt ->
94```
95
96Note that this fragment of the tree only shows four `parser::Expr` nodes,
97but the full parse tree also contained a fifth `parser::Expr` node for the
98constant 216 in the statement:
99
100```fortran
101      dummyArg = 216
102```
103## Analysis and implementation planning
104
105I then considered what I needed to do.  I needed to detect situations where an
106active 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
108message that highlighted the erroneous source code.
109
110### Deciding where to add the code to the compiler
111This new semantic check would depend on several types of information -- the
112parse tree, source code location information, symbols, and expressions.  Thus I
113needed to put my new code in a place in the compiler after the parse tree had
114been created, name resolution had already happened, and expression semantic
115checking had already taken place.
116
117Most semantic checks for statements are implemented by walking the parse tree
118and performing analysis on the nodes they visit.  My plan was to use this
119method.  The infrastructure for walking the parse tree for statement semantic
120checking is implemented in the files `lib/Semantics/semantics.cpp`.
121Here's a fragment of the declaration of the framework's parse tree visitor from
122`lib/Semantics/semantics.cpp`:
123
124```C++
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... {
131  public:
132    using C::Enter...;
133    using C::Leave...;
134    using BaseChecker::Enter;
135    using BaseChecker::Leave;
136    SemanticsVisitor(SemanticsContext &context)
137      : C{context}..., context_{context} {}
138      ...
139
140```
141
142Since FUNCTION calls are a kind of expression, I was planning to base my
143implementation on the contents of `parser::Expr` nodes.  I would need to define
144either an `Enter()` or `Leave()` function whose parameter was a `parser::Expr`
145node.  Here's the declaration I put into `lib/Semantics/check-do.h`:
146
147```C++
148  void Leave(const parser::Expr &);
149```
150The `Enter()` functions get called at the time the node is first visited --
151that is, before its children.  The `Leave()` function gets called after the
152children are visited.  For my check the visitation order didn't matter, so I
153arbitrarily chose to implement the `Leave()` function to visit the parse tree
154node.
155
156Since my semantic check was focused on DO CONCURRENT statements, I added it to
157the file `lib/Semantics/check-do.cpp` where most of the semantic checking for
158DO statements already lived.
159
160### Taking advantage of prior work
161When implementing a similar check for SUBROUTINE calls, I created a utility
162functions in `lib/Semantics/semantics.cpp` to emit messages if
163a symbol corresponding to an active DO variable was being potentially modified:
164
165```C++
166  void WarnDoVarRedefine(const parser::CharBlock &location, const Symbol &var);
167  void CheckDoVarRedefine(const parser::CharBlock &location, const Symbol &var);
168```
169
170The first function is intended for dummy arguments of `INTENT(INOUT)` and
171the second for `INTENT(OUT)`.
172
173Thus I needed three pieces of
174information --
1751. the source location of the erroneous text,
1762. the `INTENT` of the associated dummy argument, and
1773. the relevant symbol passed as the actual argument.
178
179The first and third are needed since they're required to call the utility
180functions.  The second is needed to determine whether to call them.
181
182### Finding the source location
183The source code location information that I'd need for the error message must
184come from the parse tree.  I looked in the file
185`include/flang/Parser/parse-tree.h` and determined that a `struct Expr`
186contained source location information since it had the field `CharBlock
187source`.  Thus, if I visited a `parser::Expr` node, I could get the source
188location information for the associated expression.
189
190### Determining the `INTENT`
191I knew that I could find the `INTENT` of the dummy argument associated with the
192actual argument from the function called `dummyIntent()` in the class
193`evaluate::ActualArgument` in the file `include/flang/Evaluate/call.h`.  So
194if 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
199  constructs.
200
201In my prior work on checking the INTENT of arguments for SUBROUTINE calls,
202the parse tree held a node for the call (a `parser::CallStmt`) that contained
203an `evaluate::ProcedureRef` node.
204```C++
205  struct CallStmt {
206    WRAPPER_CLASS_BOILERPLATE(CallStmt, Call);
207    mutable std::unique_ptr<evaluate::ProcedureRef,
208        common::Deleter<evaluate::ProcedureRef>>
209        typedCall;  // filled by semantics
210  };
211```
212The `evaluate::ProcedureRef` contains a list of `evaluate::ActualArgument`
213nodes.  I could then find the INTENT of a dummy argument from the
214`evaluate::ActualArgument` node.
215
216For a FUNCTION call, though, there is no similar way to get from a parse tree
217node to an `evaluate::ProcedureRef` node.  But I knew that there was an
218existing framework used in DO construct semantic checking that traversed an
219`evaluate::Expr` node collecting `semantics::Symbol` nodes.  I guessed that I'd
220be able to use a similar framework to traverse an `evaluate::Expr`  node to
221find all of the `evaluate::ActualArgument` nodes.
222
223Note 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
226maps directly to the source code and has fields that specify any operators in
227the expression, the operands, and the source position of the expression.
228
229Additionally, in the namespace `evaluate`, there are `evaluate::Expr<T>`
230template classes defined in the file `include/flang/Evaluate/expression.h`.
231These are parameterized over the various types of Fortran and constitute a
232suite of strongly-typed representations of valid Fortran expressions of type
233`T` that have been fully elaborated with conversion operations and subjected to
234constant folding.  After an expression has undergone semantic analysis, the
235field `typedExpr` in the `parser::Expr` node is filled in with a pointer that
236owns an instance of `evaluate::Expr<SomeType>`, the most general representation
237of an analyzed expression.
238
239All of the declarations associated with both FUNCTION and SUBROUTINE calls are
240in `include/flang/Evaluate/call.h`.  An `evaluate::FunctionRef` inherits from
241an `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
244only needed to find the `evaluate::ActualArgument` nodes in an expression.
245They hold all of the information I needed.
246
247So my plan was to start with the `parser::Expr` node and extract its
248associated `evaluate::Expr` field.  I would then traverse the
249`evaluate::Expr` tree collecting all of the `evaluate::ActualArgument`
250nodes.  I would look at each of these nodes to determine the `INTENT` of
251the associated dummy argument.
252
253This combination of the traversal framework and `dummyIntent()` would give
254me the `INTENT` of all of the dummy arguments in a FUNCTION call.  Thus, I
255would have the second piece of information I needed.
256
257### Determining if the actual argument is a variable
258I also guessed that I could determine if the `evaluate::ActualArgument`
259consisted of a variable.
260
261Once I had a symbol for the variable, I could call one of the functions:
262```C++
263  void WarnDoVarRedefine(const parser::CharBlock &, const Symbol &);
264  void CheckDoVarRedefine(const parser::CharBlock &, const Symbol &);
265```
266to emit the messages.
267
268If my plans worked out, this would give me the three pieces of information I
269needed -- the source location of the erroneous text, the `INTENT` of the dummy
270argument, and a symbol that I could use to determine whether the actual
271argument was an active DO variable.
272
273## Implementation
274
275### Adding a parse tree visitor
276I started my implementation by adding a visitor for `parser::Expr` nodes.
277Since 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
279verify that my new code was actually getting executed.
280
281In `lib/Semantics/check-do.h`, I added the declaration for the visitor:
282
283```C++
284  void Leave(const parser::Expr &);
285```
286
287In `lib/Semantics/check-do.cpp`, I added an (almost empty) implementation:
288
289```C++
290  void DoChecker::Leave(const parser::Expr &) {
291    std::cout << "In Leave for parser::Expr\n";
292  }
293```
294
295I then built the compiler with these changes and ran it on my test program.
296This time, I made sure to invoke semantic checking.  Here's the command I used:
297```bash
298  f18 -fdebug-resolve-names -fdebug-dump-parse-tree -funparse-with-symbols testfun.f90
299```
300
301This produced the output:
302
303```
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
309```
310
311This made sense since the parse tree contained five `parser::Expr` nodes.
312So far, so good.  Note that a `parse::Expr` node has a field with the
313source position of the associated expression (`CharBlock source`).  So I
314now had one of the three pieces of information needed to detect and report
315errors.
316
317### Collecting the actual arguments
318To get the `INTENT` of the dummy arguments and the `semantics::Symbol` associated with the
319actual argument, I needed to find all of the actual arguments embedded in an
320expression that contained a FUNCTION call.  So my next step was to write the
321framework to walk the `evaluate::Expr` to gather all of the
322`evaluate::ActualArgument` nodes.  The code that I planned to model it on
323was 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`:
326
327```C++
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 {
334      return {symbol};
335    }
336  };
337  template<typename A> semantics::SymbolSet CollectSymbols(const A &x) {
338    return CollectSymbolsHelper{}(x);
339  }
340```
341
342Note that the `CollectSymbols()` function returns a `semantics::Symbolset`,
343which is declared in `include/flang/Semantics/symbol.h`:
344
345```C++
346  using SymbolSet = std::set<SymbolRef>;
347```
348
349This infrastructure yields a collection based on `std::set<>`.  Using an
350`std::set<>` means that if the same object is inserted twice, the
351collection only gets one copy.  This was the behavior that I wanted.
352
353Here's a sample invocation of `CollectSymbols()` that I found:
354```C++
355    if (const auto *expr{GetExpr(parsedExpr)}) {
356      for (const Symbol &symbol : evaluate::CollectSymbols(*expr)) {
357```
358
359I 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
361full `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
363support sets that contain references.  This limitation is part of the rationale
364for the f18 implementation of type `common::Reference`, which is defined in
365  `include/flang/Common/reference.h`.
366
367`SymbolRef`, the specialization of the template `common::Reference` for
368`semantics::Symbol`, is declared in the file
369`include/flang/Semantics/symbol.h`:
370
371```C++
372  using SymbolRef = common::Reference<const Symbol>;
373```
374
375So to implement something that would collect `evaluate::ActualArgument`
376nodes from an `evaluate::Expr`, I first defined the required types
377`ActualArgumentRef` and `ActualArgumentSet`.  Since these are being
378used exclusively for DO construct semantic checking (currently), I put their
379definitions into `lib/Semantics/check-do.cpp`:
380
381
382```C++
383  namespace Fortran::evaluate {
384    using ActualArgumentRef = common::Reference<const ActualArgument>;
385  }
386
387
388  using ActualArgumentSet = std::set<evaluate::ActualArgumentRef>;
389```
390
391Since `ActualArgument` is in the namespace `evaluate`, I put the
392definition for `ActualArgumentRef` in that namespace, too.
393
394I then modeled the code to create an `ActualArgumentSet` after the code to
395collect a `SymbolSet` and put it into `lib/Semantics/check-do.cpp`:
396
397
398```C++
399  struct CollectActualArgumentsHelper
400    : public evaluate::SetTraverse<CollectActualArgumentsHelper,
401          ActualArgumentSet> {
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};
407    }
408  };
409
410  template<typename A> ActualArgumentSet CollectActualArguments(const A &x) {
411    return CollectActualArgumentsHelper{}(x);
412  }
413
414  template ActualArgumentSet CollectActualArguments(const SomeExpr &);
415```
416
417Unfortunately, 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.
419To fix this, I added a definition for `<`.  I didn't care how `<` was
420defined, so I just used the address of the object:
421
422```C++
423  inline bool operator<(ActualArgumentRef x, ActualArgumentRef y) {
424    return &*x < &*y;
425  }
426```
427
428I was surprised when this did not make the error message saying that I needed
429the `<` operator go away.  Eventually, I figured out that the definition of
430the `<` operator needed to be in the `evaluate` namespace.  Once I put
431it there, everything compiled successfully.  Here's the code that worked:
432
433```C++
434  namespace Fortran::evaluate {
435  using ActualArgumentRef = common::Reference<const ActualArgument>;
436
437  inline bool operator<(ActualArgumentRef x, ActualArgumentRef y) {
438    return &*x < &*y;
439  }
440  }
441```
442
443I then modified my visitor for the parser::Expr to invoke my new collection
444framework.  To verify that it was actually doing something, I printed out the
445number of `evaluate::ActualArgument` nodes that it collected.  Note the
446call to `GetExpr()` in the invocation of `CollectActualArguments()`.  I
447modeled this on similar code that collected a `SymbolSet` described above:
448
449```C++
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";
454  }
455```
456
457I compiled and tested this code on my little test program.  Here's the output that I got:
458```
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
469```
470
471So most of the `parser::Expr`nodes contained no actual arguments, but the
472fourth expression in the parse tree walk contained a single argument.  This may
473seem wrong since the third `parser::Expr` node in the file contains the
474`FunctionReference` node along with the arguments that we're gathering.
475But since the tree walk function is being called upon leaving a
476`parser::Expr` node, the function visits the `parser::Expr` node
477associated with the `parser::ActualArg` node before it visits the
478`parser::Expr` node associated with the `parser::FunctionReference`
479node.
480
481So far, so good.
482
483### Finding the `INTENT` of the dummy argument
484I now wanted to find the `INTENT` of the dummy argument associated with the
485arguments in the set.  As mentioned earlier, the type
486`evaluate::ActualArgument` has a member function called `dummyIntent()`
487that gives this value.  So I augmented my code to print out the `INTENT`:
488
489```C++
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()};
496      switch (intent) {
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";
501      }
502    }
503  }
504```
505
506I then rebuilt my compiler and ran it on my test case.  This produced the following output:
507
508```
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
517  INTENT(OUT)
518  In Leave for parser::Expr
519  Number of arguments: 0
520```
521
522I then modified my test case to convince myself that I was getting the correct
523`INTENT` for `IN`, `INOUT`, and default cases.
524
525So far, so good.
526
527### Finding the symbols for arguments that are variables
528The third and last piece of information I needed was to determine if a variable
529was being passed as an actual argument.  In such cases, I wanted to get the
530symbol table node (`semantics::Symbol`) for the variable.  My starting point was the
531`evaluate::ActualArgument` node.
532
533I was unsure of how to do this, so I browsed through existing code to look for
534how 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
535uses of `ActualArgument`.  One of the first hits I got was in `lib/Evaluate/call.cpp` in the definition of `ActualArgument::GetType()`:
536
537```C++
538std::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();
543  } else {
544    return std::nullopt;
545  }
546}
547```
548
549I noted the call to `UnwrapExpr()` that yielded a value of
550`Expr<SomeType>`.  So I guessed that I could use this member function to
551get an `evaluate::Expr<SomeType>` on which I could perform further analysis.
552
553I also knew that the header file `include/flang/Evaluate/tools.h` held many
554utility functions for dealing with `evaluate::Expr` objects.  I was hoping to
555find something that would determine if an `evaluate::Expr` was a variable.  So
556I searched for `IsVariable` and got a hit immediately.
557```C++
558  template<typename A> bool IsVariable(const A &x) {
559    if (auto known{IsVariableHelper{}(x)}) {
560      return *known;
561    } else {
562      return false;
563    }
564  }
565```
566
567But I actually needed more than just the knowledge that an `evaluate::Expr` was
568a variable.  I needed the `semantics::Symbol` associated with the variable.  So
569I searched in `include/flang/Evaluate/tools.h` for functions that returned a
570`semantics::Symbol`.  I found the following:
571
572```C++
573// If an expression is simply a whole symbol data designator,
574// extract and return that symbol, else null.
575template<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)}) {
578      return &p->get();
579    }
580  }
581  return nullptr;
582}
583```
584
585This was exactly what I wanted.  DO variables must be whole symbols.  So I
586could try to extract a whole `semantics::Symbol` from the `evaluate::Expr` in my
587`evaluate::ActualArgument`.  If this extraction resulted in a `semantics::Symbol`
588that wasn't a `nullptr`, I could then conclude if it was a variable that I
589could pass to existing functions that would determine if it was an active DO
590variable.
591
592I then modified the compiler to perform the analysis that I'd guessed would
593work:
594
595```C++
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";
605        }
606      }
607      common::Intent intent{argRef->dummyIntent()};
608      switch (intent) {
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";
613      }
614    }
615  }
616```
617
618Note the line that prints out the symbol table entry for the variable:
619
620```C++
621          std::cout << "Found a whole variable: " << *var << "\n";
622```
623
624The compiler defines the "<<" operator for `semantics::Symbol`, which is handy
625for analyzing the compiler's behavior.
626
627Here's the result of running the modified compiler on my Fortran test case:
628
629```
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)
640  INTENT(OUT)
641  In Leave for parser::Expr
642  Number of arguments: 0
643```
644
645Sweet.
646
647### Emitting the messages
648At this point, using the source location information from the original
649`parser::Expr`, I had enough information to plug into the exiting
650interfaces for emitting messages for active DO variables.  I modified the
651compiler code accordingly:
652
653
654```C++
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()};
665          switch (intent) {
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);
670              break;
671            case common::Intent::InOut:
672              std::cout << "INTENT(INOUT)\n";
673              context_.WarnDoVarRedefine(parsedExpr.source, *var);
674              break;
675            default: std::cout << "default INTENT\n";
676          }
677        }
678      }
679    }
680  }
681```
682
683I then ran this code on my test case, and miraculously, got the following
684output:
685
686```
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)
697  INTENT(OUT)
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)
702               ^^^^^^^^^^^^^^^^^^^
703  testfun.f90:5:6: Enclosing DO construct
704      do ivar = 1, 10
705         ^^^^
706```
707
708Even sweeter.
709
710## Improving the test case
711At this point, my implementation seemed to be working.  But I was concerned
712about the limitations of my test case.  So I augmented it to include arguments
713other than `INTENT(OUT)` and more complex expressions.  Luckily, my
714augmented test did not reveal any new problems.
715
716Here's the test I ended up with:
717
718```Fortran
719  subroutine s()
720
721    Integer :: ivar, jvar
722
723    ! This one is OK
724    do ivar = 1, 10
725      jvar = intentInFunc(ivar)
726    end do
727
728    ! Error for passing a DO variable to an INTENT(OUT) dummy
729    do ivar = 1, 10
730      jvar = intentOutFunc(ivar)
731    end do
732
733    ! Error for passing a DO variable to an INTENT(OUT) dummy, more complex
734    ! expression
735    do ivar = 1, 10
736      jvar = 83 + intentInFunc(intentOutFunc(ivar))
737    end do
738
739    ! Warning for passing a DO variable to an INTENT(INOUT) dummy
740    do ivar = 1, 10
741      jvar = intentInOutFunc(ivar)
742    end do
743
744  contains
745    function intentInFunc(dummyArg)
746      integer, intent(in) :: dummyArg
747      integer  :: intentInFunc
748
749      intentInFunc = 343
750    end function intentInFunc
751
752    function intentOutFunc(dummyArg)
753      integer, intent(out) :: dummyArg
754      integer  :: intentOutFunc
755
756      dummyArg = 216
757      intentOutFunc = 343
758    end function intentOutFunc
759
760    function intentInOutFunc(dummyArg)
761      integer, intent(inout) :: dummyArg
762      integer  :: intentInOutFunc
763
764      dummyArg = 216
765      intentInOutFunc = 343
766    end function intentInOutFunc
767
768  end subroutine s
769```
770
771## Submitting the pull request
772At this point, my implementation seemed functionally complete, so I stripped out all of the debug statements, ran `clang-format` on it and reviewed it
773to make sure that the names were clear.  Here's what I ended up with:
774
775```C++
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()};
782          switch (intent) {
783            case common::Intent::Out:
784              context_.CheckDoVarRedefine(parsedExpr.source, *var);
785              break;
786            case common::Intent::InOut:
787              context_.WarnDoVarRedefine(parsedExpr.source, *var);
788              break;
789            default:; // INTENT(IN) or default intent
790          }
791        }
792      }
793    }
794  }
795```
796
797I then created a pull request to get review comments.
798
799## Responding to pull request comments
800I 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
802code I'd previously writted to do a similar check for SUBROUTINE calls to see
803if there was an opportunity to share code.  This examination resulted in
804  converting my existing code to the following pair of functions:
805
806
807```C++
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);
816          } else {
817            context.WarnDoVarRedefine(location, *var);  // INTENT(INOUT)
818          }
819        }
820      }
821    }
822  }
823
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_);
829      }
830    }
831  }
832```
833
834The function `CheckIfArgIsDoVar()` was shared with the checks for DO
835variables being passed to SUBROUTINE calls.
836
837At this point, my pull request was approved, and I merged it and deleted the
838associated branch.
839