2015-09-28 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / ada / par_sco.adb
blob8593dab63d287a58805c506bcf2fcab6de3c2dcc
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- P A R _ S C O --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 2009-2015, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Aspects; use Aspects;
27 with Atree; use Atree;
28 with Debug; use Debug;
29 with Errout; use Errout;
30 with Lib; use Lib;
31 with Lib.Util; use Lib.Util;
32 with Namet; use Namet;
33 with Nlists; use Nlists;
34 with Opt; use Opt;
35 with Output; use Output;
36 with Put_SCOs;
37 with SCOs; use SCOs;
38 with Sem; use Sem;
39 with Sem_Util; use Sem_Util;
40 with Sinfo; use Sinfo;
41 with Sinput; use Sinput;
42 with Snames; use Snames;
43 with Table;
45 with GNAT.HTable; use GNAT.HTable;
46 with GNAT.Heap_Sort_G;
47 with GNAT.Table;
49 package body Par_SCO is
51 --------------------------
52 -- First-pass SCO table --
53 --------------------------
55 -- The Short_Circuit_And_Or pragma enables one to use AND and OR operators
56 -- in source code while the ones used with booleans will be interpreted as
57 -- their short circuit alternatives (AND THEN and OR ELSE). Thus, the true
58 -- meaning of these operators is known only after the semantic analysis.
60 -- However, decision SCOs include short circuit operators only. The SCO
61 -- information generation pass must be done before expansion, hence before
62 -- the semantic analysis. Because of this, the SCO information generation
63 -- is done in two passes.
65 -- The first one (SCO_Record_Raw, before semantic analysis) completes the
66 -- SCO_Raw_Table assuming all AND/OR operators are short circuit ones.
67 -- Then, the semantic analysis determines which operators are promoted to
68 -- short circuit ones. Finally, the second pass (SCO_Record_Filtered)
69 -- translates the SCO_Raw_Table to SCO_Table, taking care of removing the
70 -- remaining AND/OR operators and of adjusting decisions accordingly
71 -- (splitting decisions, removing empty ones, etc.).
73 type SCO_Generation_State_Type is (None, Raw, Filtered);
74 SCO_Generation_State : SCO_Generation_State_Type := None;
75 -- Keep track of the SCO generation state: this will prevent us from
76 -- running some steps multiple times (the second pass has to be started
77 -- from multiple places).
79 package SCO_Raw_Table is new GNAT.Table (
80 Table_Component_Type => SCO_Table_Entry,
81 Table_Index_Type => Nat,
82 Table_Low_Bound => 1,
83 Table_Initial => 500,
84 Table_Increment => 300);
86 -----------------------
87 -- Unit Number Table --
88 -----------------------
90 -- This table parallels the SCO_Unit_Table, keeping track of the unit
91 -- numbers corresponding to the entries made in this table, so that before
92 -- writing out the SCO information to the ALI file, we can fill in the
93 -- proper dependency numbers and file names.
95 -- Note that the zero'th entry is here for convenience in sorting the
96 -- table, the real lower bound is 1.
98 package SCO_Unit_Number_Table is new Table.Table (
99 Table_Component_Type => Unit_Number_Type,
100 Table_Index_Type => SCO_Unit_Index,
101 Table_Low_Bound => 0, -- see note above on sort
102 Table_Initial => 20,
103 Table_Increment => 200,
104 Table_Name => "SCO_Unit_Number_Entry");
106 ------------------------------------------
107 -- Condition/Operator/Pragma Hash Table --
108 ------------------------------------------
110 -- We need to be able to get to conditions quickly for handling the calls
111 -- to Set_SCO_Condition efficiently, and similarly to get to pragmas to
112 -- handle calls to Set_SCO_Pragma_Enabled (the same holds for operators and
113 -- Set_SCO_Logical_Operator). For this purpose we identify the conditions,
114 -- operators and pragmas in the table by their starting sloc, and use this
115 -- hash table to map from these sloc values to SCO_Table indexes.
117 type Header_Num is new Integer range 0 .. 996;
118 -- Type for hash table headers
120 function Hash (F : Source_Ptr) return Header_Num;
121 -- Function to Hash source pointer value
123 function Equal (F1, F2 : Source_Ptr) return Boolean;
124 -- Function to test two keys for equality
126 function "<" (S1, S2 : Source_Location) return Boolean;
127 -- Function to test for source locations order
129 package SCO_Raw_Hash_Table is new Simple_HTable
130 (Header_Num, Int, 0, Source_Ptr, Hash, Equal);
131 -- The actual hash table
133 --------------------------
134 -- Internal Subprograms --
135 --------------------------
137 function Has_Decision (N : Node_Id) return Boolean;
138 -- N is the node for a subexpression. Returns True if the subexpression
139 -- contains a nested decision (i.e. either is a logical operator, or
140 -- contains a logical operator in its subtree).
142 -- This must be used in the first pass (SCO_Record_Raw) only: here AND/OR
143 -- operators are considered as short circuit, just in case the
144 -- Short_Circuit_And_Or pragma is used: only real short circuit operations
145 -- will be kept in the secord pass.
147 type Tristate is (False, True, Unknown);
149 function Is_Logical_Operator (N : Node_Id) return Tristate;
150 -- N is the node for a subexpression. This procedure determines whether N
151 -- is a logical operator: True for short circuit conditions, Unknown for OR
152 -- and AND (the Short_Circuit_And_Or pragma may be used) and False
153 -- otherwise. Note that in cases where True is returned, callers assume
154 -- Nkind (N) in N_Op.
156 function To_Source_Location (S : Source_Ptr) return Source_Location;
157 -- Converts Source_Ptr value to Source_Location (line/col) format
159 procedure Process_Decisions
160 (N : Node_Id;
161 T : Character;
162 Pragma_Sloc : Source_Ptr);
163 -- If N is Empty, has no effect. Otherwise scans the tree for the node N,
164 -- to output any decisions it contains. T is one of IEGPWX (for context of
165 -- expression: if/exit when/entry guard/pragma/while/expression). If T is
166 -- other than X, the node N is the if expression involved, and a decision
167 -- is always present (at the very least a simple decision is present at the
168 -- top level).
170 procedure Process_Decisions
171 (L : List_Id;
172 T : Character;
173 Pragma_Sloc : Source_Ptr);
174 -- Calls above procedure for each element of the list L
176 procedure Set_Raw_Table_Entry
177 (C1 : Character;
178 C2 : Character;
179 From : Source_Ptr;
180 To : Source_Ptr;
181 Last : Boolean;
182 Pragma_Sloc : Source_Ptr := No_Location;
183 Pragma_Aspect_Name : Name_Id := No_Name);
184 -- Append an entry to SCO_Raw_Table with fields set as per arguments
186 type Dominant_Info is record
187 K : Character;
188 -- F/T/S/E for a valid dominance marker, or ' ' for no dominant
190 N : Node_Id;
191 -- Node providing the Sloc(s) for the dominance marker
192 end record;
193 No_Dominant : constant Dominant_Info := (' ', Empty);
195 procedure Record_Instance (Id : Instance_Id; Inst_Sloc : Source_Ptr);
196 -- Add one entry from the instance table to the corresponding SCO table
198 procedure Traverse_Declarations_Or_Statements
199 (L : List_Id;
200 D : Dominant_Info := No_Dominant;
201 P : Node_Id := Empty);
202 -- Process L, a list of statements or declarations dominated by D.
203 -- If P is present, it is processed as though it had been prepended to L.
205 function Traverse_Declarations_Or_Statements
206 (L : List_Id;
207 D : Dominant_Info := No_Dominant;
208 P : Node_Id := Empty) return Dominant_Info;
209 -- Same as above, and returns dominant information corresponding to the
210 -- last node with SCO in L.
212 -- The following Traverse_* routines perform appropriate calls to
213 -- Traverse_Declarations_Or_Statements to traverse specific node kinds.
214 -- Parameter D, when present, indicates the dominant of the first
215 -- declaration or statement within N.
217 -- Why is Traverse_Sync_Definition commented specificaly and
218 -- the others are not???
220 procedure Traverse_Generic_Package_Declaration (N : Node_Id);
221 procedure Traverse_Handled_Statement_Sequence
222 (N : Node_Id;
223 D : Dominant_Info := No_Dominant);
224 procedure Traverse_Package_Body (N : Node_Id);
225 procedure Traverse_Package_Declaration
226 (N : Node_Id;
227 D : Dominant_Info := No_Dominant);
228 procedure Traverse_Subprogram_Or_Task_Body
229 (N : Node_Id;
230 D : Dominant_Info := No_Dominant);
232 procedure Traverse_Sync_Definition (N : Node_Id);
233 -- Traverse a protected definition or task definition
235 procedure Write_SCOs_To_ALI_File is new Put_SCOs;
236 -- Write SCO information to the ALI file using routines in Lib.Util
238 ----------
239 -- dsco --
240 ----------
242 procedure dsco is
243 procedure Dump_Entry (Index : Nat; T : SCO_Table_Entry);
244 -- Dump a SCO table entry
246 ----------------
247 -- Dump_Entry --
248 ----------------
250 procedure Dump_Entry (Index : Nat; T : SCO_Table_Entry) is
251 begin
252 Write_Str (" ");
253 Write_Int (Index);
254 Write_Char ('.');
256 if T.C1 /= ' ' then
257 Write_Str (" C1 = '");
258 Write_Char (T.C1);
259 Write_Char (''');
260 end if;
262 if T.C2 /= ' ' then
263 Write_Str (" C2 = '");
264 Write_Char (T.C2);
265 Write_Char (''');
266 end if;
268 if T.From /= No_Source_Location then
269 Write_Str (" From = ");
270 Write_Int (Int (T.From.Line));
271 Write_Char (':');
272 Write_Int (Int (T.From.Col));
273 end if;
275 if T.To /= No_Source_Location then
276 Write_Str (" To = ");
277 Write_Int (Int (T.To.Line));
278 Write_Char (':');
279 Write_Int (Int (T.To.Col));
280 end if;
282 if T.Last then
283 Write_Str (" True");
284 else
285 Write_Str (" False");
286 end if;
288 Write_Eol;
289 end Dump_Entry;
291 -- Start of processing for dsco
293 begin
294 -- Dump SCO unit table
296 Write_Line ("SCO Unit Table");
297 Write_Line ("--------------");
299 for Index in 1 .. SCO_Unit_Table.Last loop
300 declare
301 UTE : SCO_Unit_Table_Entry renames SCO_Unit_Table.Table (Index);
303 begin
304 Write_Str (" ");
305 Write_Int (Int (Index));
306 Write_Str (" Dep_Num = ");
307 Write_Int (Int (UTE.Dep_Num));
308 Write_Str (" From = ");
309 Write_Int (Int (UTE.From));
310 Write_Str (" To = ");
311 Write_Int (Int (UTE.To));
313 Write_Str (" File_Name = """);
315 if UTE.File_Name /= null then
316 Write_Str (UTE.File_Name.all);
317 end if;
319 Write_Char ('"');
320 Write_Eol;
321 end;
322 end loop;
324 -- Dump SCO Unit number table if it contains any entries
326 if SCO_Unit_Number_Table.Last >= 1 then
327 Write_Eol;
328 Write_Line ("SCO Unit Number Table");
329 Write_Line ("---------------------");
331 for Index in 1 .. SCO_Unit_Number_Table.Last loop
332 Write_Str (" ");
333 Write_Int (Int (Index));
334 Write_Str (". Unit_Number = ");
335 Write_Int (Int (SCO_Unit_Number_Table.Table (Index)));
336 Write_Eol;
337 end loop;
338 end if;
340 -- Dump SCO raw-table
342 Write_Eol;
343 Write_Line ("SCO Raw Table");
344 Write_Line ("---------");
346 if SCO_Generation_State = Filtered then
347 Write_Line ("Empty (free'd after second pass)");
348 else
349 for Index in 1 .. SCO_Raw_Table.Last loop
350 Dump_Entry (Index, SCO_Raw_Table.Table (Index));
351 end loop;
352 end if;
354 -- Dump SCO table itself
356 Write_Eol;
357 Write_Line ("SCO Filtered Table");
358 Write_Line ("---------");
360 for Index in 1 .. SCO_Table.Last loop
361 Dump_Entry (Index, SCO_Table.Table (Index));
362 end loop;
363 end dsco;
365 -----------
366 -- Equal --
367 -----------
369 function Equal (F1, F2 : Source_Ptr) return Boolean is
370 begin
371 return F1 = F2;
372 end Equal;
374 -------
375 -- < --
376 -------
378 function "<" (S1, S2 : Source_Location) return Boolean is
379 begin
380 return S1.Line < S2.Line
381 or else (S1.Line = S2.Line and then S1.Col < S2.Col);
382 end "<";
384 ------------------
385 -- Has_Decision --
386 ------------------
388 function Has_Decision (N : Node_Id) return Boolean is
390 function Check_Node (N : Node_Id) return Traverse_Result;
391 -- Determine if Nkind (N) indicates the presence of a decision (i.e.
392 -- N is a logical operator, which is a decision in itself, or an
393 -- IF-expression whose Condition attribute is a decision).
395 ----------------
396 -- Check_Node --
397 ----------------
399 function Check_Node (N : Node_Id) return Traverse_Result is
400 begin
401 -- If we are not sure this is a logical operator (AND and OR may be
402 -- turned into logical operators with the Short_Circuit_And_Or
403 -- pragma), assume it is. Putative decisions will be discarded if
404 -- needed in the secord pass.
406 if Is_Logical_Operator (N) /= False
407 or else Nkind (N) = N_If_Expression
408 then
409 return Abandon;
410 else
411 return OK;
412 end if;
413 end Check_Node;
415 function Traverse is new Traverse_Func (Check_Node);
417 -- Start of processing for Has_Decision
419 begin
420 return Traverse (N) = Abandon;
421 end Has_Decision;
423 ----------
424 -- Hash --
425 ----------
427 function Hash (F : Source_Ptr) return Header_Num is
428 begin
429 return Header_Num (Nat (F) mod 997);
430 end Hash;
432 ----------------
433 -- Initialize --
434 ----------------
436 procedure Initialize is
437 begin
438 SCO_Unit_Number_Table.Init;
440 -- The SCO_Unit_Number_Table entry with index 0 is intentionally set
441 -- aside to be used as temporary for sorting.
443 SCO_Unit_Number_Table.Increment_Last;
444 end Initialize;
446 -------------------------
447 -- Is_Logical_Operator --
448 -------------------------
450 function Is_Logical_Operator (N : Node_Id) return Tristate is
451 begin
452 if Nkind_In (N, N_Op_Not, N_And_Then, N_Or_Else) then
453 return True;
454 elsif Nkind_In (N, N_Op_And, N_Op_Or) then
455 return Unknown;
456 else
457 return False;
458 end if;
459 end Is_Logical_Operator;
461 -----------------------
462 -- Process_Decisions --
463 -----------------------
465 -- Version taking a list
467 procedure Process_Decisions
468 (L : List_Id;
469 T : Character;
470 Pragma_Sloc : Source_Ptr)
472 N : Node_Id;
473 begin
474 if L /= No_List then
475 N := First (L);
476 while Present (N) loop
477 Process_Decisions (N, T, Pragma_Sloc);
478 Next (N);
479 end loop;
480 end if;
481 end Process_Decisions;
483 -- Version taking a node
485 Current_Pragma_Sloc : Source_Ptr := No_Location;
486 -- While processing a pragma, this is set to the sloc of the N_Pragma node
488 procedure Process_Decisions
489 (N : Node_Id;
490 T : Character;
491 Pragma_Sloc : Source_Ptr)
493 Mark : Nat;
494 -- This is used to mark the location of a decision sequence in the SCO
495 -- table. We use it for backing out a simple decision in an expression
496 -- context that contains only NOT operators.
498 Mark_Hash : Nat;
499 -- Likewise for the putative SCO_Raw_Hash_Table entries: see below
501 type Hash_Entry is record
502 Sloc : Source_Ptr;
503 SCO_Index : Nat;
504 end record;
505 -- We must register all conditions/pragmas in SCO_Raw_Hash_Table.
506 -- However we cannot register them in the same time we are adding the
507 -- corresponding SCO entries to the raw table since we may discard them
508 -- later on. So instead we put all putative conditions into Hash_Entries
509 -- (see below) and register them once we are sure we keep them.
511 -- This data structure holds the conditions/pragmas to register in
512 -- SCO_Raw_Hash_Table.
514 package Hash_Entries is new Table.Table (
515 Table_Component_Type => Hash_Entry,
516 Table_Index_Type => Nat,
517 Table_Low_Bound => 1,
518 Table_Initial => 10,
519 Table_Increment => 10,
520 Table_Name => "Hash_Entries");
521 -- Hold temporarily (i.e. free'd before returning) the Hash_Entry before
522 -- they are registered in SCO_Raw_Hash_Table.
524 X_Not_Decision : Boolean;
525 -- This flag keeps track of whether a decision sequence in the SCO table
526 -- contains only NOT operators, and is for an expression context (T=X).
527 -- The flag will be set False if T is other than X, or if an operator
528 -- other than NOT is in the sequence.
530 function Process_Node (N : Node_Id) return Traverse_Result;
531 -- Processes one node in the traversal, looking for logical operators,
532 -- and if one is found, outputs the appropriate table entries.
534 procedure Output_Decision_Operand (N : Node_Id);
535 -- The node N is the top level logical operator of a decision, or it is
536 -- one of the operands of a logical operator belonging to a single
537 -- complex decision. This routine outputs the sequence of table entries
538 -- corresponding to the node. Note that we do not process the sub-
539 -- operands to look for further decisions, that processing is done in
540 -- Process_Decision_Operand, because we can't get decisions mixed up in
541 -- the global table. Call has no effect if N is Empty.
543 procedure Output_Element (N : Node_Id);
544 -- Node N is an operand of a logical operator that is not itself a
545 -- logical operator, or it is a simple decision. This routine outputs
546 -- the table entry for the element, with C1 set to ' '. Last is set
547 -- False, and an entry is made in the condition hash table.
549 procedure Output_Header (T : Character);
550 -- Outputs a decision header node. T is I/W/E/P for IF/WHILE/EXIT WHEN/
551 -- PRAGMA, and 'X' for the expression case.
553 procedure Process_Decision_Operand (N : Node_Id);
554 -- This is called on node N, the top level node of a decision, or on one
555 -- of its operands or suboperands after generating the full output for
556 -- the complex decision. It process the suboperands of the decision
557 -- looking for nested decisions.
559 -----------------------------
560 -- Output_Decision_Operand --
561 -----------------------------
563 procedure Output_Decision_Operand (N : Node_Id) is
564 C1, C2 : Character;
565 -- C1 holds a character that identifies the operation while C2
566 -- indicates whether we are sure (' ') or not ('?') this operation
567 -- belongs to the decision. '?' entries will be filtered out in the
568 -- second (SCO_Record_Filtered) pass.
570 L : Node_Id;
571 T : Tristate;
573 begin
574 if No (N) then
575 return;
576 end if;
578 T := Is_Logical_Operator (N);
580 -- Logical operator
582 if T /= False then
583 if Nkind (N) = N_Op_Not then
584 C1 := '!';
585 L := Empty;
587 else
588 L := Left_Opnd (N);
590 if Nkind_In (N, N_Op_Or, N_Or_Else) then
591 C1 := '|';
592 else pragma Assert (Nkind_In (N, N_Op_And, N_And_Then));
593 C1 := '&';
594 end if;
595 end if;
597 if T = True then
598 C2 := ' ';
599 else
600 C2 := '?';
601 end if;
603 Set_Raw_Table_Entry
604 (C1 => C1,
605 C2 => C2,
606 From => Sloc (N),
607 To => No_Location,
608 Last => False);
610 Hash_Entries.Append ((Sloc (N), SCO_Raw_Table.Last));
612 Output_Decision_Operand (L);
613 Output_Decision_Operand (Right_Opnd (N));
615 -- Not a logical operator
617 else
618 Output_Element (N);
619 end if;
620 end Output_Decision_Operand;
622 --------------------
623 -- Output_Element --
624 --------------------
626 procedure Output_Element (N : Node_Id) is
627 FSloc : Source_Ptr;
628 LSloc : Source_Ptr;
629 begin
630 Sloc_Range (N, FSloc, LSloc);
631 Set_Raw_Table_Entry
632 (C1 => ' ',
633 C2 => 'c',
634 From => FSloc,
635 To => LSloc,
636 Last => False);
637 Hash_Entries.Append ((FSloc, SCO_Raw_Table.Last));
638 end Output_Element;
640 -------------------
641 -- Output_Header --
642 -------------------
644 procedure Output_Header (T : Character) is
645 Loc : Source_Ptr := No_Location;
646 -- Node whose Sloc is used for the decision
648 Nam : Name_Id := No_Name;
649 -- For the case of an aspect, aspect name
651 begin
652 case T is
653 when 'I' | 'E' | 'W' | 'a' | 'A' =>
655 -- For IF, EXIT, WHILE, or aspects, the token SLOC is that of
656 -- the parent of the expression.
658 Loc := Sloc (Parent (N));
660 if T = 'a' or else T = 'A' then
661 Nam := Chars (Identifier (Parent (N)));
662 end if;
664 when 'G' | 'P' =>
666 -- For entry guard, the token sloc is from the N_Entry_Body.
667 -- For PRAGMA, we must get the location from the pragma node.
668 -- Argument N is the pragma argument, and we have to go up
669 -- two levels (through the pragma argument association) to
670 -- get to the pragma node itself. For the guard on a select
671 -- alternative, we do not have access to the token location for
672 -- the WHEN, so we use the first sloc of the condition itself
673 -- (note: we use First_Sloc, not Sloc, because this is what is
674 -- referenced by dominance markers).
676 -- Doesn't this requirement of using First_Sloc need to be
677 -- documented in the spec ???
679 if Nkind_In (Parent (N), N_Accept_Alternative,
680 N_Delay_Alternative,
681 N_Terminate_Alternative)
682 then
683 Loc := First_Sloc (N);
684 else
685 Loc := Sloc (Parent (Parent (N)));
686 end if;
688 when 'X' =>
690 -- For an expression, no Sloc
692 null;
694 -- No other possibilities
696 when others =>
697 raise Program_Error;
698 end case;
700 Set_Raw_Table_Entry
701 (C1 => T,
702 C2 => ' ',
703 From => Loc,
704 To => No_Location,
705 Last => False,
706 Pragma_Sloc => Pragma_Sloc,
707 Pragma_Aspect_Name => Nam);
709 -- For an aspect specification, which will be rewritten into a
710 -- pragma, enter a hash table entry now.
712 if T = 'a' then
713 Hash_Entries.Append ((Loc, SCO_Raw_Table.Last));
714 end if;
715 end Output_Header;
717 ------------------------------
718 -- Process_Decision_Operand --
719 ------------------------------
721 procedure Process_Decision_Operand (N : Node_Id) is
722 begin
723 if Is_Logical_Operator (N) /= False then
724 if Nkind (N) /= N_Op_Not then
725 Process_Decision_Operand (Left_Opnd (N));
726 X_Not_Decision := False;
727 end if;
729 Process_Decision_Operand (Right_Opnd (N));
731 else
732 Process_Decisions (N, 'X', Pragma_Sloc);
733 end if;
734 end Process_Decision_Operand;
736 ------------------
737 -- Process_Node --
738 ------------------
740 function Process_Node (N : Node_Id) return Traverse_Result is
741 begin
742 case Nkind (N) is
744 -- Logical operators, output table entries and then process
745 -- operands recursively to deal with nested conditions.
747 when N_And_Then | N_Or_Else | N_Op_Not | N_Op_And | N_Op_Or =>
748 declare
749 T : Character;
751 begin
752 -- If outer level, then type comes from call, otherwise it
753 -- is more deeply nested and counts as X for expression.
755 if N = Process_Decisions.N then
756 T := Process_Decisions.T;
757 else
758 T := 'X';
759 end if;
761 -- Output header for sequence
763 X_Not_Decision := T = 'X' and then Nkind (N) = N_Op_Not;
764 Mark := SCO_Raw_Table.Last;
765 Mark_Hash := Hash_Entries.Last;
766 Output_Header (T);
768 -- Output the decision
770 Output_Decision_Operand (N);
772 -- If the decision was in an expression context (T = 'X')
773 -- and contained only NOT operators, then we don't output
774 -- it, so delete it.
776 if X_Not_Decision then
777 SCO_Raw_Table.Set_Last (Mark);
778 Hash_Entries.Set_Last (Mark_Hash);
780 -- Otherwise, set Last in last table entry to mark end
782 else
783 SCO_Raw_Table.Table (SCO_Raw_Table.Last).Last := True;
784 end if;
786 -- Process any embedded decisions
788 Process_Decision_Operand (N);
789 return Skip;
790 end;
792 -- Case expression
794 -- Really hard to believe this is correct given the special
795 -- handling for if expressions below ???
797 when N_Case_Expression =>
798 return OK; -- ???
800 -- If expression, processed like an if statement
802 when N_If_Expression =>
803 declare
804 Cond : constant Node_Id := First (Expressions (N));
805 Thnx : constant Node_Id := Next (Cond);
806 Elsx : constant Node_Id := Next (Thnx);
807 begin
808 Process_Decisions (Cond, 'I', Pragma_Sloc);
809 Process_Decisions (Thnx, 'X', Pragma_Sloc);
810 Process_Decisions (Elsx, 'X', Pragma_Sloc);
811 return Skip;
812 end;
814 -- All other cases, continue scan
816 when others =>
817 return OK;
819 end case;
820 end Process_Node;
822 procedure Traverse is new Traverse_Proc (Process_Node);
824 -- Start of processing for Process_Decisions
826 begin
827 if No (N) then
828 return;
829 end if;
831 Hash_Entries.Init;
833 -- See if we have simple decision at outer level and if so then
834 -- generate the decision entry for this simple decision. A simple
835 -- decision is a boolean expression (which is not a logical operator
836 -- or short circuit form) appearing as the operand of an IF, WHILE,
837 -- EXIT WHEN, or special PRAGMA construct.
839 if T /= 'X' and then Is_Logical_Operator (N) = False then
840 Output_Header (T);
841 Output_Element (N);
843 -- Change Last in last table entry to True to mark end of
844 -- sequence, which is this case is only one element long.
846 SCO_Raw_Table.Table (SCO_Raw_Table.Last).Last := True;
847 end if;
849 Traverse (N);
851 -- Now we have the definitive set of SCO entries, register them in the
852 -- corresponding hash table.
854 for I in 1 .. Hash_Entries.Last loop
855 SCO_Raw_Hash_Table.Set
856 (Hash_Entries.Table (I).Sloc,
857 Hash_Entries.Table (I).SCO_Index);
858 end loop;
859 Hash_Entries.Free;
860 end Process_Decisions;
862 -----------
863 -- pscos --
864 -----------
866 procedure pscos is
868 procedure Write_Info_Char (C : Character) renames Write_Char;
869 -- Write one character;
871 procedure Write_Info_Initiate (Key : Character) renames Write_Char;
872 -- Start new one and write one character;
874 procedure Write_Info_Nat (N : Nat);
875 -- Write value of N
877 procedure Write_Info_Terminate renames Write_Eol;
878 -- Terminate current line
880 --------------------
881 -- Write_Info_Nat --
882 --------------------
884 procedure Write_Info_Nat (N : Nat) is
885 begin
886 Write_Int (N);
887 end Write_Info_Nat;
889 procedure Debug_Put_SCOs is new Put_SCOs;
891 -- Start of processing for pscos
893 begin
894 Debug_Put_SCOs;
895 end pscos;
897 ---------------------
898 -- Record_Instance --
899 ---------------------
901 procedure Record_Instance (Id : Instance_Id; Inst_Sloc : Source_Ptr) is
902 Inst_Src : constant Source_File_Index :=
903 Get_Source_File_Index (Inst_Sloc);
904 begin
905 SCO_Instance_Table.Append
906 ((Inst_Dep_Num => Dependency_Num (Unit (Inst_Src)),
907 Inst_Loc => To_Source_Location (Inst_Sloc),
908 Enclosing_Instance => SCO_Instance_Index (Instance (Inst_Src))));
909 pragma Assert
910 (SCO_Instance_Table.Last = SCO_Instance_Index (Id));
911 end Record_Instance;
913 ----------------
914 -- SCO_Output --
915 ----------------
917 procedure SCO_Output is
918 procedure Populate_SCO_Instance_Table is
919 new Sinput.Iterate_On_Instances (Record_Instance);
920 begin
921 pragma Assert (SCO_Generation_State = Filtered);
923 if Debug_Flag_Dot_OO then
924 dsco;
925 end if;
927 Populate_SCO_Instance_Table;
929 -- Sort the unit tables based on dependency numbers
931 Unit_Table_Sort : declare
933 function Lt (Op1, Op2 : Natural) return Boolean;
934 -- Comparison routine for sort call
936 procedure Move (From : Natural; To : Natural);
937 -- Move routine for sort call
939 --------
940 -- Lt --
941 --------
943 function Lt (Op1, Op2 : Natural) return Boolean is
944 begin
945 return
946 Dependency_Num
947 (SCO_Unit_Number_Table.Table (SCO_Unit_Index (Op1)))
949 Dependency_Num
950 (SCO_Unit_Number_Table.Table (SCO_Unit_Index (Op2)));
951 end Lt;
953 ----------
954 -- Move --
955 ----------
957 procedure Move (From : Natural; To : Natural) is
958 begin
959 SCO_Unit_Table.Table (SCO_Unit_Index (To)) :=
960 SCO_Unit_Table.Table (SCO_Unit_Index (From));
961 SCO_Unit_Number_Table.Table (SCO_Unit_Index (To)) :=
962 SCO_Unit_Number_Table.Table (SCO_Unit_Index (From));
963 end Move;
965 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
967 -- Start of processing for Unit_Table_Sort
969 begin
970 Sorting.Sort (Integer (SCO_Unit_Table.Last));
971 end Unit_Table_Sort;
973 -- Loop through entries in the unit table to set file name and
974 -- dependency number entries.
976 for J in 1 .. SCO_Unit_Table.Last loop
977 declare
978 U : constant Unit_Number_Type := SCO_Unit_Number_Table.Table (J);
979 UTE : SCO_Unit_Table_Entry renames SCO_Unit_Table.Table (J);
980 begin
981 Get_Name_String (Reference_Name (Source_Index (U)));
982 UTE.File_Name := new String'(Name_Buffer (1 .. Name_Len));
983 UTE.Dep_Num := Dependency_Num (U);
984 end;
985 end loop;
987 -- Now the tables are all setup for output to the ALI file
989 Write_SCOs_To_ALI_File;
990 end SCO_Output;
992 -------------------------
993 -- SCO_Pragma_Disabled --
994 -------------------------
996 function SCO_Pragma_Disabled (Loc : Source_Ptr) return Boolean is
997 Index : Nat;
999 begin
1000 if Loc = No_Location then
1001 return False;
1002 end if;
1004 Index := SCO_Raw_Hash_Table.Get (Loc);
1006 -- The test here for zero is to deal with possible previous errors, and
1007 -- for the case of pragma statement SCOs, for which we always set the
1008 -- Pragma_Sloc even if the particular pragma cannot be specifically
1009 -- disabled.
1011 if Index /= 0 then
1012 declare
1013 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1015 begin
1016 case T.C1 is
1017 when 'S' =>
1018 -- Pragma statement
1020 return T.C2 = 'p';
1022 when 'A' =>
1023 -- Aspect decision (enabled)
1025 return False;
1027 when 'a' =>
1028 -- Aspect decision (not enabled)
1030 return True;
1032 when ASCII.NUL =>
1033 -- Nullified disabled SCO
1035 return True;
1037 when others =>
1038 raise Program_Error;
1039 end case;
1040 end;
1042 else
1043 return False;
1044 end if;
1045 end SCO_Pragma_Disabled;
1047 --------------------
1048 -- SCO_Record_Raw --
1049 --------------------
1051 procedure SCO_Record_Raw (U : Unit_Number_Type) is
1052 Lu : Node_Id;
1053 From : Nat;
1055 procedure Traverse_Aux_Decls (N : Node_Id);
1056 -- Traverse the Aux_Decls_Node of compilation unit N
1058 ------------------------
1059 -- Traverse_Aux_Decls --
1060 ------------------------
1062 procedure Traverse_Aux_Decls (N : Node_Id) is
1063 ADN : constant Node_Id := Aux_Decls_Node (N);
1064 begin
1065 Traverse_Declarations_Or_Statements (Config_Pragmas (ADN));
1066 Traverse_Declarations_Or_Statements (Pragmas_After (ADN));
1068 -- Declarations and Actions do not correspond to source constructs,
1069 -- they contain only nodes from expansion, so at this point they
1070 -- should still be empty:
1072 pragma Assert (No (Declarations (ADN)));
1073 pragma Assert (No (Actions (ADN)));
1074 end Traverse_Aux_Decls;
1076 -- Start of processing for SCO_Record_Raw
1078 begin
1079 -- It is legitimate to run this pass multiple times (once per unit) so
1080 -- run it even if it was already run before.
1082 pragma Assert (SCO_Generation_State in None .. Raw);
1083 SCO_Generation_State := Raw;
1085 -- Ignore call if not generating code and generating SCO's
1087 if not (Generate_SCO and then Operating_Mode = Generate_Code) then
1088 return;
1089 end if;
1091 -- Ignore call if this unit already recorded
1093 for J in 1 .. SCO_Unit_Number_Table.Last loop
1094 if U = SCO_Unit_Number_Table.Table (J) then
1095 return;
1096 end if;
1097 end loop;
1099 -- Otherwise record starting entry
1101 From := SCO_Raw_Table.Last + 1;
1103 -- Get Unit (checking case of subunit)
1105 Lu := Unit (Cunit (U));
1107 if Nkind (Lu) = N_Subunit then
1108 Lu := Proper_Body (Lu);
1109 end if;
1111 -- Traverse the unit
1113 Traverse_Aux_Decls (Cunit (U));
1115 case Nkind (Lu) is
1116 when
1117 N_Package_Declaration |
1118 N_Package_Body |
1119 N_Subprogram_Declaration |
1120 N_Subprogram_Body |
1121 N_Generic_Package_Declaration |
1122 N_Protected_Body |
1123 N_Task_Body |
1124 N_Generic_Instantiation =>
1126 Traverse_Declarations_Or_Statements (L => No_List, P => Lu);
1128 when others =>
1130 -- All other cases of compilation units (e.g. renamings), generate
1131 -- no SCO information.
1133 null;
1134 end case;
1136 -- Make entry for new unit in unit tables, we will fill in the file
1137 -- name and dependency numbers later.
1139 SCO_Unit_Table.Append (
1140 (Dep_Num => 0,
1141 File_Name => null,
1142 File_Index => Get_Source_File_Index (Sloc (Lu)),
1143 From => From,
1144 To => SCO_Raw_Table.Last));
1146 SCO_Unit_Number_Table.Append (U);
1147 end SCO_Record_Raw;
1149 -----------------------
1150 -- Set_SCO_Condition --
1151 -----------------------
1153 procedure Set_SCO_Condition (Cond : Node_Id; Val : Boolean) is
1155 -- SCO annotations are not processed after the filtering pass
1157 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1159 Orig : constant Node_Id := Original_Node (Cond);
1160 Index : Nat;
1161 Start : Source_Ptr;
1162 Dummy : Source_Ptr;
1164 Constant_Condition_Code : constant array (Boolean) of Character :=
1165 (False => 'f', True => 't');
1166 begin
1167 Sloc_Range (Orig, Start, Dummy);
1168 Index := SCO_Raw_Hash_Table.Get (Start);
1170 -- Index can be zero for boolean expressions that do not have SCOs
1171 -- (simple decisions outside of a control flow structure), or in case
1172 -- of a previous error.
1174 if Index = 0 then
1175 return;
1177 else
1178 pragma Assert (SCO_Raw_Table.Table (Index).C1 = ' ');
1179 SCO_Raw_Table.Table (Index).C2 := Constant_Condition_Code (Val);
1180 end if;
1181 end Set_SCO_Condition;
1183 ------------------------------
1184 -- Set_SCO_Logical_Operator --
1185 ------------------------------
1187 procedure Set_SCO_Logical_Operator (Op : Node_Id) is
1189 -- SCO annotations are not processed after the filtering pass
1191 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1193 Orig : constant Node_Id := Original_Node (Op);
1194 Orig_Sloc : constant Source_Ptr := Sloc (Orig);
1195 Index : constant Nat := SCO_Raw_Hash_Table.Get (Orig_Sloc);
1197 begin
1198 -- All (putative) logical operators are supposed to have their own entry
1199 -- in the SCOs table. However, the semantic analysis may invoke this
1200 -- subprogram with nodes that are out of the SCO generation scope.
1202 if Index /= 0 then
1203 SCO_Raw_Table.Table (Index).C2 := ' ';
1204 end if;
1205 end Set_SCO_Logical_Operator;
1207 ----------------------------
1208 -- Set_SCO_Pragma_Enabled --
1209 ----------------------------
1211 procedure Set_SCO_Pragma_Enabled (Loc : Source_Ptr) is
1213 -- SCO annotations are not processed after the filtering pass
1215 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1217 Index : Nat;
1219 begin
1220 -- Nothing to do if not generating SCO, or if we're not processing the
1221 -- original source occurrence of the pragma.
1223 if not (Generate_SCO
1224 and then In_Extended_Main_Source_Unit (Loc)
1225 and then not (In_Instance or In_Inlined_Body))
1226 then
1227 return;
1228 end if;
1230 -- Note: the reason we use the Sloc value as the key is that in the
1231 -- generic case, the call to this procedure is made on a copy of the
1232 -- original node, so we can't use the Node_Id value.
1234 Index := SCO_Raw_Hash_Table.Get (Loc);
1236 -- A zero index here indicates that semantic analysis found an
1237 -- activated pragma at Loc which does not have a corresponding pragma
1238 -- or aspect at the syntax level. This may occur in legitimate cases
1239 -- because of expanded code (such are Pre/Post conditions generated for
1240 -- formal parameter validity checks), or as a consequence of a previous
1241 -- error.
1243 if Index = 0 then
1244 return;
1246 else
1247 declare
1248 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1250 begin
1251 -- Note: may be called multiple times for the same sloc, so
1252 -- account for the fact that the entry may already have been
1253 -- marked enabled.
1255 case T.C1 is
1256 -- Aspect (decision SCO)
1258 when 'a' =>
1259 T.C1 := 'A';
1261 when 'A' =>
1262 null;
1264 -- Pragma (statement SCO)
1266 when 'S' =>
1267 pragma Assert (T.C2 = 'p' or else T.C2 = 'P');
1268 T.C2 := 'P';
1270 when others =>
1271 raise Program_Error;
1272 end case;
1273 end;
1274 end if;
1275 end Set_SCO_Pragma_Enabled;
1277 -------------------------
1278 -- Set_Raw_Table_Entry --
1279 -------------------------
1281 procedure Set_Raw_Table_Entry
1282 (C1 : Character;
1283 C2 : Character;
1284 From : Source_Ptr;
1285 To : Source_Ptr;
1286 Last : Boolean;
1287 Pragma_Sloc : Source_Ptr := No_Location;
1288 Pragma_Aspect_Name : Name_Id := No_Name)
1290 pragma Assert (SCO_Generation_State = Raw);
1291 begin
1292 SCO_Raw_Table.Append
1293 ((C1 => C1,
1294 C2 => C2,
1295 From => To_Source_Location (From),
1296 To => To_Source_Location (To),
1297 Last => Last,
1298 Pragma_Sloc => Pragma_Sloc,
1299 Pragma_Aspect_Name => Pragma_Aspect_Name));
1300 end Set_Raw_Table_Entry;
1302 ------------------------
1303 -- To_Source_Location --
1304 ------------------------
1306 function To_Source_Location (S : Source_Ptr) return Source_Location is
1307 begin
1308 if S = No_Location then
1309 return No_Source_Location;
1310 else
1311 return
1312 (Line => Get_Logical_Line_Number (S),
1313 Col => Get_Column_Number (S));
1314 end if;
1315 end To_Source_Location;
1317 -----------------------------------------
1318 -- Traverse_Declarations_Or_Statements --
1319 -----------------------------------------
1321 -- Tables used by Traverse_Declarations_Or_Statements for temporarily
1322 -- holding statement and decision entries. These are declared globally
1323 -- since they are shared by recursive calls to this procedure.
1325 type SC_Entry is record
1326 N : Node_Id;
1327 From : Source_Ptr;
1328 To : Source_Ptr;
1329 Typ : Character;
1330 end record;
1331 -- Used to store a single entry in the following table, From:To represents
1332 -- the range of entries in the CS line entry, and typ is the type, with
1333 -- space meaning that no type letter will accompany the entry.
1335 package SC is new Table.Table (
1336 Table_Component_Type => SC_Entry,
1337 Table_Index_Type => Nat,
1338 Table_Low_Bound => 1,
1339 Table_Initial => 1000,
1340 Table_Increment => 200,
1341 Table_Name => "SCO_SC");
1342 -- Used to store statement components for a CS entry to be output
1343 -- as a result of the call to this procedure. SC.Last is the last
1344 -- entry stored, so the current statement sequence is represented
1345 -- by SC_Array (SC_First .. SC.Last), where SC_First is saved on
1346 -- entry to each recursive call to the routine.
1348 -- Extend_Statement_Sequence adds an entry to this array, and then
1349 -- Set_Statement_Entry clears the entries starting with SC_First,
1350 -- copying these entries to the main SCO output table. The reason that
1351 -- we do the temporary caching of results in this array is that we want
1352 -- the SCO table entries for a given CS line to be contiguous, and the
1353 -- processing may output intermediate entries such as decision entries.
1355 type SD_Entry is record
1356 Nod : Node_Id;
1357 Lst : List_Id;
1358 Typ : Character;
1359 Plo : Source_Ptr;
1360 end record;
1361 -- Used to store a single entry in the following table. Nod is the node to
1362 -- be searched for decisions for the case of Process_Decisions_Defer with a
1363 -- node argument (with Lst set to No_List. Lst is the list to be searched
1364 -- for decisions for the case of Process_Decisions_Defer with a List
1365 -- argument (in which case Nod is set to Empty). Plo is the sloc of the
1366 -- enclosing pragma, if any.
1368 package SD is new Table.Table (
1369 Table_Component_Type => SD_Entry,
1370 Table_Index_Type => Nat,
1371 Table_Low_Bound => 1,
1372 Table_Initial => 1000,
1373 Table_Increment => 200,
1374 Table_Name => "SCO_SD");
1375 -- Used to store possible decision information. Instead of calling the
1376 -- Process_Decisions procedures directly, we call Process_Decisions_Defer,
1377 -- which simply stores the arguments in this table. Then when we clear
1378 -- out a statement sequence using Set_Statement_Entry, after generating
1379 -- the CS lines for the statements, the entries in this table result in
1380 -- calls to Process_Decision. The reason for doing things this way is to
1381 -- ensure that decisions are output after the CS line for the statements
1382 -- in which the decisions occur.
1384 procedure Traverse_Declarations_Or_Statements
1385 (L : List_Id;
1386 D : Dominant_Info := No_Dominant;
1387 P : Node_Id := Empty)
1389 Discard_Dom : Dominant_Info;
1390 pragma Warnings (Off, Discard_Dom);
1391 begin
1392 Discard_Dom := Traverse_Declarations_Or_Statements (L, D, P);
1393 end Traverse_Declarations_Or_Statements;
1395 function Traverse_Declarations_Or_Statements
1396 (L : List_Id;
1397 D : Dominant_Info := No_Dominant;
1398 P : Node_Id := Empty) return Dominant_Info
1400 Current_Dominant : Dominant_Info := D;
1401 -- Dominance information for the current basic block
1403 Current_Test : Node_Id;
1404 -- Conditional node (N_If_Statement or N_Elsiif being processed
1406 N : Node_Id;
1408 SC_First : constant Nat := SC.Last + 1;
1409 SD_First : constant Nat := SD.Last + 1;
1410 -- Record first entries used in SC/SD at this recursive level
1412 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character);
1413 -- Extend the current statement sequence to encompass the node N. Typ
1414 -- is the letter that identifies the type of statement/declaration that
1415 -- is being added to the sequence.
1417 procedure Set_Statement_Entry;
1418 -- Output CS entries for all statements saved in table SC, and end the
1419 -- current CS sequence. Then output entries for all decisions nested in
1420 -- these statements, which have been deferred so far.
1422 procedure Process_Decisions_Defer (N : Node_Id; T : Character);
1423 pragma Inline (Process_Decisions_Defer);
1424 -- This routine is logically the same as Process_Decisions, except that
1425 -- the arguments are saved in the SD table for later processing when
1426 -- Set_Statement_Entry is called, which goes through the saved entries
1427 -- making the corresponding calls to Process_Decision.
1429 procedure Process_Decisions_Defer (L : List_Id; T : Character);
1430 pragma Inline (Process_Decisions_Defer);
1431 -- Same case for list arguments, deferred call to Process_Decisions
1433 procedure Traverse_One (N : Node_Id);
1434 -- Traverse one declaration or statement
1436 procedure Traverse_Aspects (N : Node_Id);
1437 -- Helper for Traverse_One: traverse N's aspect specifications
1439 -------------------------
1440 -- Set_Statement_Entry --
1441 -------------------------
1443 procedure Set_Statement_Entry is
1444 SC_Last : constant Int := SC.Last;
1445 SD_Last : constant Int := SD.Last;
1447 begin
1448 -- Output statement entries from saved entries in SC table
1450 for J in SC_First .. SC_Last loop
1451 if J = SC_First then
1453 if Current_Dominant /= No_Dominant then
1454 declare
1455 From, To : Source_Ptr;
1456 begin
1457 Sloc_Range (Current_Dominant.N, From, To);
1458 if Current_Dominant.K /= 'E' then
1459 To := No_Location;
1460 end if;
1461 Set_Raw_Table_Entry
1462 (C1 => '>',
1463 C2 => Current_Dominant.K,
1464 From => From,
1465 To => To,
1466 Last => False,
1467 Pragma_Sloc => No_Location,
1468 Pragma_Aspect_Name => No_Name);
1469 end;
1470 end if;
1471 end if;
1473 declare
1474 SCE : SC_Entry renames SC.Table (J);
1475 Pragma_Sloc : Source_Ptr := No_Location;
1476 Pragma_Aspect_Name : Name_Id := No_Name;
1477 begin
1478 -- For the case of a statement SCO for a pragma controlled by
1479 -- Set_SCO_Pragma_Enabled, set Pragma_Sloc so that the SCO (and
1480 -- those of any nested decision) is emitted only if the pragma
1481 -- is enabled.
1483 if SCE.Typ = 'p' then
1484 Pragma_Sloc := SCE.From;
1485 SCO_Raw_Hash_Table.Set
1486 (Pragma_Sloc, SCO_Raw_Table.Last + 1);
1487 Pragma_Aspect_Name := Pragma_Name (SCE.N);
1488 pragma Assert (Pragma_Aspect_Name /= No_Name);
1490 elsif SCE.Typ = 'P' then
1491 Pragma_Aspect_Name := Pragma_Name (SCE.N);
1492 pragma Assert (Pragma_Aspect_Name /= No_Name);
1493 end if;
1495 Set_Raw_Table_Entry
1496 (C1 => 'S',
1497 C2 => SCE.Typ,
1498 From => SCE.From,
1499 To => SCE.To,
1500 Last => (J = SC_Last),
1501 Pragma_Sloc => Pragma_Sloc,
1502 Pragma_Aspect_Name => Pragma_Aspect_Name);
1503 end;
1504 end loop;
1506 -- Last statement of basic block, if present, becomes new current
1507 -- dominant.
1509 if SC_Last >= SC_First then
1510 Current_Dominant := ('S', SC.Table (SC_Last).N);
1511 end if;
1513 -- Clear out used section of SC table
1515 SC.Set_Last (SC_First - 1);
1517 -- Output any embedded decisions
1519 for J in SD_First .. SD_Last loop
1520 declare
1521 SDE : SD_Entry renames SD.Table (J);
1522 begin
1523 if Present (SDE.Nod) then
1524 Process_Decisions (SDE.Nod, SDE.Typ, SDE.Plo);
1525 else
1526 Process_Decisions (SDE.Lst, SDE.Typ, SDE.Plo);
1527 end if;
1528 end;
1529 end loop;
1531 -- Clear out used section of SD table
1533 SD.Set_Last (SD_First - 1);
1534 end Set_Statement_Entry;
1536 -------------------------------
1537 -- Extend_Statement_Sequence --
1538 -------------------------------
1540 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character) is
1541 F : Source_Ptr;
1542 T : Source_Ptr;
1543 Dummy : Source_Ptr;
1544 To_Node : Node_Id := Empty;
1546 begin
1547 Sloc_Range (N, F, T);
1549 case Nkind (N) is
1550 when N_Accept_Statement =>
1551 if Present (Parameter_Specifications (N)) then
1552 To_Node := Last (Parameter_Specifications (N));
1553 elsif Present (Entry_Index (N)) then
1554 To_Node := Entry_Index (N);
1555 end if;
1557 when N_Case_Statement =>
1558 To_Node := Expression (N);
1560 when N_If_Statement | N_Elsif_Part =>
1561 To_Node := Condition (N);
1563 when N_Extended_Return_Statement =>
1564 To_Node := Last (Return_Object_Declarations (N));
1566 when N_Loop_Statement =>
1567 To_Node := Iteration_Scheme (N);
1569 when N_Selective_Accept |
1570 N_Timed_Entry_Call |
1571 N_Conditional_Entry_Call |
1572 N_Asynchronous_Select |
1573 N_Single_Protected_Declaration |
1574 N_Single_Task_Declaration =>
1575 T := F;
1577 when N_Protected_Type_Declaration | N_Task_Type_Declaration =>
1578 if Has_Aspects (N) then
1579 To_Node := Last (Aspect_Specifications (N));
1581 elsif Present (Discriminant_Specifications (N)) then
1582 To_Node := Last (Discriminant_Specifications (N));
1584 else
1585 To_Node := Defining_Identifier (N);
1586 end if;
1588 when others =>
1589 null;
1591 end case;
1593 if Present (To_Node) then
1594 Sloc_Range (To_Node, Dummy, T);
1595 end if;
1597 SC.Append ((N, F, T, Typ));
1598 end Extend_Statement_Sequence;
1600 -----------------------------
1601 -- Process_Decisions_Defer --
1602 -----------------------------
1604 procedure Process_Decisions_Defer (N : Node_Id; T : Character) is
1605 begin
1606 SD.Append ((N, No_List, T, Current_Pragma_Sloc));
1607 end Process_Decisions_Defer;
1609 procedure Process_Decisions_Defer (L : List_Id; T : Character) is
1610 begin
1611 SD.Append ((Empty, L, T, Current_Pragma_Sloc));
1612 end Process_Decisions_Defer;
1614 ----------------------
1615 -- Traverse_Aspects --
1616 ----------------------
1618 procedure Traverse_Aspects (N : Node_Id) is
1619 AN : Node_Id;
1620 AE : Node_Id;
1621 C1 : Character;
1623 begin
1624 AN := First (Aspect_Specifications (N));
1625 while Present (AN) loop
1626 AE := Expression (AN);
1628 -- SCOs are generated before semantic analysis/expansion:
1629 -- PPCs are not split yet.
1631 pragma Assert (not Split_PPC (AN));
1633 C1 := ASCII.NUL;
1635 case Get_Aspect_Id (AN) is
1637 -- Aspects rewritten into pragmas controlled by a Check_Policy:
1638 -- Current_Pragma_Sloc must be set to the sloc of the aspect
1639 -- specification. The corresponding pragma will have the same
1640 -- sloc.
1642 when Aspect_Pre |
1643 Aspect_Precondition |
1644 Aspect_Post |
1645 Aspect_Postcondition |
1646 Aspect_Invariant =>
1648 C1 := 'a';
1650 -- Aspects whose checks are generated in client units,
1651 -- regardless of whether or not the check is activated in the
1652 -- unit which contains the declaration: create decision as
1653 -- unconditionally enabled aspect (but still make a pragma
1654 -- entry since Set_SCO_Pragma_Enabled will be called when
1655 -- analyzing actual checks, possibly in other units).
1657 -- Pre/post can have checks in client units too because of
1658 -- inheritance, so should they be moved here???
1660 when Aspect_Predicate |
1661 Aspect_Static_Predicate |
1662 Aspect_Dynamic_Predicate |
1663 Aspect_Type_Invariant =>
1665 C1 := 'A';
1667 -- Other aspects: just process any decision nested in the
1668 -- aspect expression.
1670 when others =>
1672 if Has_Decision (AE) then
1673 C1 := 'X';
1674 end if;
1676 end case;
1678 if C1 /= ASCII.NUL then
1679 pragma Assert (Current_Pragma_Sloc = No_Location);
1681 if C1 = 'a' or else C1 = 'A' then
1682 Current_Pragma_Sloc := Sloc (AN);
1683 end if;
1685 Process_Decisions_Defer (AE, C1);
1687 Current_Pragma_Sloc := No_Location;
1688 end if;
1690 Next (AN);
1691 end loop;
1692 end Traverse_Aspects;
1694 ------------------
1695 -- Traverse_One --
1696 ------------------
1698 procedure Traverse_One (N : Node_Id) is
1699 begin
1700 -- Initialize or extend current statement sequence. Note that for
1701 -- special cases such as IF and Case statements we will modify
1702 -- the range to exclude internal statements that should not be
1703 -- counted as part of the current statement sequence.
1705 case Nkind (N) is
1707 -- Package declaration
1709 when N_Package_Declaration =>
1710 Set_Statement_Entry;
1711 Traverse_Package_Declaration (N, Current_Dominant);
1713 -- Generic package declaration
1715 when N_Generic_Package_Declaration =>
1716 Set_Statement_Entry;
1717 Traverse_Generic_Package_Declaration (N);
1719 -- Package body
1721 when N_Package_Body =>
1722 Set_Statement_Entry;
1723 Traverse_Package_Body (N);
1725 -- Subprogram declaration or subprogram body stub
1727 when N_Subprogram_Declaration | N_Subprogram_Body_Stub =>
1728 Process_Decisions_Defer
1729 (Parameter_Specifications (Specification (N)), 'X');
1731 -- Entry declaration
1733 when N_Entry_Declaration =>
1734 Process_Decisions_Defer (Parameter_Specifications (N), 'X');
1736 -- Generic subprogram declaration
1738 when N_Generic_Subprogram_Declaration =>
1739 Process_Decisions_Defer
1740 (Generic_Formal_Declarations (N), 'X');
1741 Process_Decisions_Defer
1742 (Parameter_Specifications (Specification (N)), 'X');
1744 -- Task or subprogram body
1746 when N_Task_Body | N_Subprogram_Body =>
1747 Set_Statement_Entry;
1748 Traverse_Subprogram_Or_Task_Body (N);
1750 -- Entry body
1752 when N_Entry_Body =>
1753 declare
1754 Cond : constant Node_Id :=
1755 Condition (Entry_Body_Formal_Part (N));
1757 Inner_Dominant : Dominant_Info := No_Dominant;
1759 begin
1760 Set_Statement_Entry;
1762 if Present (Cond) then
1763 Process_Decisions_Defer (Cond, 'G');
1765 -- For an entry body with a barrier, the entry body
1766 -- is dominanted by a True evaluation of the barrier.
1768 Inner_Dominant := ('T', N);
1769 end if;
1771 Traverse_Subprogram_Or_Task_Body (N, Inner_Dominant);
1772 end;
1774 -- Protected body
1776 when N_Protected_Body =>
1777 Set_Statement_Entry;
1778 Traverse_Declarations_Or_Statements (Declarations (N));
1780 -- Exit statement, which is an exit statement in the SCO sense,
1781 -- so it is included in the current statement sequence, but
1782 -- then it terminates this sequence. We also have to process
1783 -- any decisions in the exit statement expression.
1785 when N_Exit_Statement =>
1786 Extend_Statement_Sequence (N, 'E');
1787 Process_Decisions_Defer (Condition (N), 'E');
1788 Set_Statement_Entry;
1790 -- If condition is present, then following statement is
1791 -- only executed if the condition evaluates to False.
1793 if Present (Condition (N)) then
1794 Current_Dominant := ('F', N);
1795 else
1796 Current_Dominant := No_Dominant;
1797 end if;
1799 -- Label, which breaks the current statement sequence, but the
1800 -- label itself is not included in the next statement sequence,
1801 -- since it generates no code.
1803 when N_Label =>
1804 Set_Statement_Entry;
1805 Current_Dominant := No_Dominant;
1807 -- Block statement, which breaks the current statement sequence
1809 when N_Block_Statement =>
1810 Set_Statement_Entry;
1812 -- The first statement in the handled sequence of statements
1813 -- is dominated by the elaboration of the last declaration.
1815 Current_Dominant := Traverse_Declarations_Or_Statements
1816 (L => Declarations (N),
1817 D => Current_Dominant);
1819 Traverse_Handled_Statement_Sequence
1820 (N => Handled_Statement_Sequence (N),
1821 D => Current_Dominant);
1823 -- If statement, which breaks the current statement sequence,
1824 -- but we include the condition in the current sequence.
1826 when N_If_Statement =>
1827 Current_Test := N;
1828 Extend_Statement_Sequence (N, 'I');
1829 Process_Decisions_Defer (Condition (N), 'I');
1830 Set_Statement_Entry;
1832 -- Now we traverse the statements in the THEN part
1834 Traverse_Declarations_Or_Statements
1835 (L => Then_Statements (N),
1836 D => ('T', N));
1838 -- Loop through ELSIF parts if present
1840 if Present (Elsif_Parts (N)) then
1841 declare
1842 Saved_Dominant : constant Dominant_Info :=
1843 Current_Dominant;
1845 Elif : Node_Id := First (Elsif_Parts (N));
1847 begin
1848 while Present (Elif) loop
1850 -- An Elsif is executed only if the previous test
1851 -- got a FALSE outcome.
1853 Current_Dominant := ('F', Current_Test);
1855 -- Now update current test information
1857 Current_Test := Elif;
1859 -- We generate a statement sequence for the
1860 -- construct "ELSIF condition", so that we have
1861 -- a statement for the resulting decisions.
1863 Extend_Statement_Sequence (Elif, 'I');
1864 Process_Decisions_Defer (Condition (Elif), 'I');
1865 Set_Statement_Entry;
1867 -- An ELSIF part is never guaranteed to have
1868 -- been executed, following statements are only
1869 -- dominated by the initial IF statement.
1871 Current_Dominant := Saved_Dominant;
1873 -- Traverse the statements in the ELSIF
1875 Traverse_Declarations_Or_Statements
1876 (L => Then_Statements (Elif),
1877 D => ('T', Elif));
1878 Next (Elif);
1879 end loop;
1880 end;
1881 end if;
1883 -- Finally traverse the ELSE statements if present
1885 Traverse_Declarations_Or_Statements
1886 (L => Else_Statements (N),
1887 D => ('F', Current_Test));
1889 -- CASE statement, which breaks the current statement sequence,
1890 -- but we include the expression in the current sequence.
1892 when N_Case_Statement =>
1893 Extend_Statement_Sequence (N, 'C');
1894 Process_Decisions_Defer (Expression (N), 'X');
1895 Set_Statement_Entry;
1897 -- Process case branches, all of which are dominated by the
1898 -- CASE statement.
1900 declare
1901 Alt : Node_Id;
1902 begin
1903 Alt := First (Alternatives (N));
1904 while Present (Alt) loop
1905 Traverse_Declarations_Or_Statements
1906 (L => Statements (Alt),
1907 D => Current_Dominant);
1908 Next (Alt);
1909 end loop;
1910 end;
1912 -- ACCEPT statement
1914 when N_Accept_Statement =>
1915 Extend_Statement_Sequence (N, 'A');
1916 Set_Statement_Entry;
1918 -- Process sequence of statements, dominant is the ACCEPT
1919 -- statement.
1921 Traverse_Handled_Statement_Sequence
1922 (N => Handled_Statement_Sequence (N),
1923 D => Current_Dominant);
1925 -- SELECT
1927 when N_Selective_Accept =>
1928 Extend_Statement_Sequence (N, 'S');
1929 Set_Statement_Entry;
1931 -- Process alternatives
1933 declare
1934 Alt : Node_Id;
1935 Guard : Node_Id;
1936 S_Dom : Dominant_Info;
1938 begin
1939 Alt := First (Select_Alternatives (N));
1940 while Present (Alt) loop
1941 S_Dom := Current_Dominant;
1942 Guard := Condition (Alt);
1944 if Present (Guard) then
1945 Process_Decisions
1946 (Guard,
1947 'G',
1948 Pragma_Sloc => No_Location);
1949 Current_Dominant := ('T', Guard);
1950 end if;
1952 Traverse_One (Alt);
1954 Current_Dominant := S_Dom;
1955 Next (Alt);
1956 end loop;
1957 end;
1959 Traverse_Declarations_Or_Statements
1960 (L => Else_Statements (N),
1961 D => Current_Dominant);
1963 when N_Timed_Entry_Call | N_Conditional_Entry_Call =>
1964 Extend_Statement_Sequence (N, 'S');
1965 Set_Statement_Entry;
1967 -- Process alternatives
1969 Traverse_One (Entry_Call_Alternative (N));
1971 if Nkind (N) = N_Timed_Entry_Call then
1972 Traverse_One (Delay_Alternative (N));
1973 else
1974 Traverse_Declarations_Or_Statements
1975 (L => Else_Statements (N),
1976 D => Current_Dominant);
1977 end if;
1979 when N_Asynchronous_Select =>
1980 Extend_Statement_Sequence (N, 'S');
1981 Set_Statement_Entry;
1983 Traverse_One (Triggering_Alternative (N));
1984 Traverse_Declarations_Or_Statements
1985 (L => Statements (Abortable_Part (N)),
1986 D => Current_Dominant);
1988 when N_Accept_Alternative =>
1989 Traverse_Declarations_Or_Statements
1990 (L => Statements (N),
1991 D => Current_Dominant,
1992 P => Accept_Statement (N));
1994 when N_Entry_Call_Alternative =>
1995 Traverse_Declarations_Or_Statements
1996 (L => Statements (N),
1997 D => Current_Dominant,
1998 P => Entry_Call_Statement (N));
2000 when N_Delay_Alternative =>
2001 Traverse_Declarations_Or_Statements
2002 (L => Statements (N),
2003 D => Current_Dominant,
2004 P => Delay_Statement (N));
2006 when N_Triggering_Alternative =>
2007 Traverse_Declarations_Or_Statements
2008 (L => Statements (N),
2009 D => Current_Dominant,
2010 P => Triggering_Statement (N));
2012 when N_Terminate_Alternative =>
2014 -- It is dubious to emit a statement SCO for a TERMINATE
2015 -- alternative, since no code is actually executed if the
2016 -- alternative is selected -- the tasking runtime call just
2017 -- never returns???
2019 Extend_Statement_Sequence (N, ' ');
2020 Set_Statement_Entry;
2022 -- Unconditional exit points, which are included in the current
2023 -- statement sequence, but then terminate it
2025 when N_Requeue_Statement |
2026 N_Goto_Statement |
2027 N_Raise_Statement =>
2028 Extend_Statement_Sequence (N, ' ');
2029 Set_Statement_Entry;
2030 Current_Dominant := No_Dominant;
2032 -- Simple return statement. which is an exit point, but we
2033 -- have to process the return expression for decisions.
2035 when N_Simple_Return_Statement =>
2036 Extend_Statement_Sequence (N, ' ');
2037 Process_Decisions_Defer (Expression (N), 'X');
2038 Set_Statement_Entry;
2039 Current_Dominant := No_Dominant;
2041 -- Extended return statement
2043 when N_Extended_Return_Statement =>
2044 Extend_Statement_Sequence (N, 'R');
2045 Process_Decisions_Defer
2046 (Return_Object_Declarations (N), 'X');
2047 Set_Statement_Entry;
2049 Traverse_Handled_Statement_Sequence
2050 (N => Handled_Statement_Sequence (N),
2051 D => Current_Dominant);
2053 Current_Dominant := No_Dominant;
2055 -- Loop ends the current statement sequence, but we include
2056 -- the iteration scheme if present in the current sequence.
2057 -- But the body of the loop starts a new sequence, since it
2058 -- may not be executed as part of the current sequence.
2060 when N_Loop_Statement =>
2061 declare
2062 ISC : constant Node_Id := Iteration_Scheme (N);
2063 Inner_Dominant : Dominant_Info := No_Dominant;
2065 begin
2066 if Present (ISC) then
2068 -- If iteration scheme present, extend the current
2069 -- statement sequence to include the iteration scheme
2070 -- and process any decisions it contains.
2072 -- While loop
2074 if Present (Condition (ISC)) then
2075 Extend_Statement_Sequence (N, 'W');
2076 Process_Decisions_Defer (Condition (ISC), 'W');
2078 -- Set more specific dominant for inner statements
2079 -- (the control sloc for the decision is that of
2080 -- the WHILE token).
2082 Inner_Dominant := ('T', ISC);
2084 -- For loop
2086 else
2087 Extend_Statement_Sequence (N, 'F');
2088 Process_Decisions_Defer
2089 (Loop_Parameter_Specification (ISC), 'X');
2090 end if;
2091 end if;
2093 Set_Statement_Entry;
2095 if Inner_Dominant = No_Dominant then
2096 Inner_Dominant := Current_Dominant;
2097 end if;
2099 Traverse_Declarations_Or_Statements
2100 (L => Statements (N),
2101 D => Inner_Dominant);
2102 end;
2104 -- Pragma
2106 when N_Pragma =>
2108 -- Record sloc of pragma (pragmas don't nest)
2110 pragma Assert (Current_Pragma_Sloc = No_Location);
2111 Current_Pragma_Sloc := Sloc (N);
2113 -- Processing depends on the kind of pragma
2115 declare
2116 Nam : constant Name_Id := Pragma_Name (N);
2117 Arg : Node_Id :=
2118 First (Pragma_Argument_Associations (N));
2119 Typ : Character;
2121 begin
2122 case Nam is
2123 when Name_Assert |
2124 Name_Assert_And_Cut |
2125 Name_Assume |
2126 Name_Check |
2127 Name_Loop_Invariant |
2128 Name_Precondition |
2129 Name_Postcondition =>
2131 -- For Assert/Check/Precondition/Postcondition, we
2132 -- must generate a P entry for the decision. Note
2133 -- that this is done unconditionally at this stage.
2134 -- Output for disabled pragmas is suppressed later
2135 -- on when we output the decision line in Put_SCOs,
2136 -- depending on setting by Set_SCO_Pragma_Enabled.
2138 if Nam = Name_Check then
2139 Next (Arg);
2140 end if;
2142 Process_Decisions_Defer (Expression (Arg), 'P');
2143 Typ := 'p';
2145 -- Pre/postconditions can be inherited so SCO should
2146 -- never be deactivated???
2148 when Name_Debug =>
2149 if Present (Arg) and then Present (Next (Arg)) then
2151 -- Case of a dyadic pragma Debug: first argument
2152 -- is a P decision, any nested decision in the
2153 -- second argument is an X decision.
2155 Process_Decisions_Defer (Expression (Arg), 'P');
2156 Next (Arg);
2157 end if;
2159 Process_Decisions_Defer (Expression (Arg), 'X');
2160 Typ := 'p';
2162 -- For all other pragmas, we generate decision entries
2163 -- for any embedded expressions, and the pragma is
2164 -- never disabled.
2166 -- Should generate P decisions (not X) for assertion
2167 -- related pragmas: [Type_]Invariant,
2168 -- [{Static,Dynamic}_]Predicate???
2170 when others =>
2171 Process_Decisions_Defer (N, 'X');
2172 Typ := 'P';
2173 end case;
2175 -- Add statement SCO
2177 Extend_Statement_Sequence (N, Typ);
2179 Current_Pragma_Sloc := No_Location;
2180 end;
2182 -- Object declaration. Ignored if Prev_Ids is set, since the
2183 -- parser generates multiple instances of the whole declaration
2184 -- if there is more than one identifier declared, and we only
2185 -- want one entry in the SCOs, so we take the first, for which
2186 -- Prev_Ids is False.
2188 when N_Object_Declaration | N_Number_Declaration =>
2189 if not Prev_Ids (N) then
2190 Extend_Statement_Sequence (N, 'o');
2192 if Has_Decision (N) then
2193 Process_Decisions_Defer (N, 'X');
2194 end if;
2195 end if;
2197 -- All other cases, which extend the current statement sequence
2198 -- but do not terminate it, even if they have nested decisions.
2200 when N_Protected_Type_Declaration | N_Task_Type_Declaration =>
2201 Extend_Statement_Sequence (N, 't');
2202 Process_Decisions_Defer (Discriminant_Specifications (N), 'X');
2203 Set_Statement_Entry;
2205 Traverse_Sync_Definition (N);
2207 when N_Single_Protected_Declaration | N_Single_Task_Declaration =>
2208 Extend_Statement_Sequence (N, 'o');
2209 Set_Statement_Entry;
2211 Traverse_Sync_Definition (N);
2213 when others =>
2215 -- Determine required type character code, or ASCII.NUL if
2216 -- no SCO should be generated for this node.
2218 declare
2219 NK : constant Node_Kind := Nkind (N);
2220 Typ : Character;
2222 begin
2223 case NK is
2224 when N_Full_Type_Declaration |
2225 N_Incomplete_Type_Declaration |
2226 N_Private_Type_Declaration |
2227 N_Private_Extension_Declaration =>
2228 Typ := 't';
2230 when N_Subtype_Declaration =>
2231 Typ := 's';
2233 when N_Renaming_Declaration =>
2234 Typ := 'r';
2236 when N_Generic_Instantiation =>
2237 Typ := 'i';
2239 when N_Representation_Clause |
2240 N_Use_Package_Clause |
2241 N_Use_Type_Clause |
2242 N_Package_Body_Stub |
2243 N_Task_Body_Stub |
2244 N_Protected_Body_Stub =>
2245 Typ := ASCII.NUL;
2247 when N_Procedure_Call_Statement =>
2248 Typ := ' ';
2250 when others =>
2251 if NK in N_Statement_Other_Than_Procedure_Call then
2252 Typ := ' ';
2253 else
2254 Typ := 'd';
2255 end if;
2256 end case;
2258 if Typ /= ASCII.NUL then
2259 Extend_Statement_Sequence (N, Typ);
2260 end if;
2261 end;
2263 -- Process any embedded decisions
2265 if Has_Decision (N) then
2266 Process_Decisions_Defer (N, 'X');
2267 end if;
2268 end case;
2270 -- Process aspects if present
2272 Traverse_Aspects (N);
2273 end Traverse_One;
2275 -- Start of processing for Traverse_Declarations_Or_Statements
2277 begin
2278 -- Process single prefixed node
2280 if Present (P) then
2281 Traverse_One (P);
2282 end if;
2284 -- Loop through statements or declarations
2286 if Is_Non_Empty_List (L) then
2287 N := First (L);
2288 while Present (N) loop
2290 -- Note: For separate bodies, we see the tree after Par.Labl has
2291 -- introduced implicit labels, so we need to ignore those nodes.
2293 if Nkind (N) /= N_Implicit_Label_Declaration then
2294 Traverse_One (N);
2295 end if;
2297 Next (N);
2298 end loop;
2300 end if;
2302 -- End sequence of statements and flush deferred decisions
2304 if Present (P) or else Is_Non_Empty_List (L) then
2305 Set_Statement_Entry;
2306 end if;
2308 return Current_Dominant;
2309 end Traverse_Declarations_Or_Statements;
2311 ------------------------------------------
2312 -- Traverse_Generic_Package_Declaration --
2313 ------------------------------------------
2315 procedure Traverse_Generic_Package_Declaration (N : Node_Id) is
2316 begin
2317 Process_Decisions (Generic_Formal_Declarations (N), 'X', No_Location);
2318 Traverse_Package_Declaration (N);
2319 end Traverse_Generic_Package_Declaration;
2321 -----------------------------------------
2322 -- Traverse_Handled_Statement_Sequence --
2323 -----------------------------------------
2325 procedure Traverse_Handled_Statement_Sequence
2326 (N : Node_Id;
2327 D : Dominant_Info := No_Dominant)
2329 Handler : Node_Id;
2331 begin
2332 -- For package bodies without a statement part, the parser adds an empty
2333 -- one, to normalize the representation. The null statement therein,
2334 -- which does not come from source, does not get a SCO.
2336 if Present (N) and then Comes_From_Source (N) then
2337 Traverse_Declarations_Or_Statements (Statements (N), D);
2339 if Present (Exception_Handlers (N)) then
2340 Handler := First (Exception_Handlers (N));
2341 while Present (Handler) loop
2342 Traverse_Declarations_Or_Statements
2343 (L => Statements (Handler),
2344 D => ('E', Handler));
2345 Next (Handler);
2346 end loop;
2347 end if;
2348 end if;
2349 end Traverse_Handled_Statement_Sequence;
2351 ---------------------------
2352 -- Traverse_Package_Body --
2353 ---------------------------
2355 procedure Traverse_Package_Body (N : Node_Id) is
2356 Dom : Dominant_Info;
2357 begin
2358 -- The first statement in the handled sequence of statements is
2359 -- dominated by the elaboration of the last declaration.
2361 Dom := Traverse_Declarations_Or_Statements (Declarations (N));
2363 Traverse_Handled_Statement_Sequence
2364 (Handled_Statement_Sequence (N), Dom);
2365 end Traverse_Package_Body;
2367 ----------------------------------
2368 -- Traverse_Package_Declaration --
2369 ----------------------------------
2371 procedure Traverse_Package_Declaration
2372 (N : Node_Id;
2373 D : Dominant_Info := No_Dominant)
2375 Spec : constant Node_Id := Specification (N);
2376 Dom : Dominant_Info;
2378 begin
2379 Dom :=
2380 Traverse_Declarations_Or_Statements (Visible_Declarations (Spec), D);
2382 -- First private declaration is dominated by last visible declaration
2384 Traverse_Declarations_Or_Statements (Private_Declarations (Spec), Dom);
2385 end Traverse_Package_Declaration;
2387 ------------------------------
2388 -- Traverse_Sync_Definition --
2389 ------------------------------
2391 procedure Traverse_Sync_Definition (N : Node_Id) is
2392 Dom_Info : Dominant_Info := ('S', N);
2393 -- The first declaration is dominated by the protected or task [type]
2394 -- declaration.
2396 Sync_Def : Node_Id;
2397 -- N's protected or task definition
2399 Vis_Decl : List_Id;
2400 -- Sync_Def's Visible_Declarations
2402 begin
2403 case Nkind (N) is
2404 when N_Single_Protected_Declaration | N_Protected_Type_Declaration =>
2405 Sync_Def := Protected_Definition (N);
2407 when N_Single_Task_Declaration | N_Task_Type_Declaration =>
2408 Sync_Def := Task_Definition (N);
2410 when others =>
2411 raise Program_Error;
2412 end case;
2414 Vis_Decl := Visible_Declarations (Sync_Def);
2416 Dom_Info := Traverse_Declarations_Or_Statements
2417 (L => Vis_Decl,
2418 D => Dom_Info);
2420 -- If visible declarations are present, the first private declaration
2421 -- is dominated by the last visible declaration.
2423 Traverse_Declarations_Or_Statements
2424 (L => Private_Declarations (Sync_Def),
2425 D => Dom_Info);
2426 end Traverse_Sync_Definition;
2428 --------------------------------------
2429 -- Traverse_Subprogram_Or_Task_Body --
2430 --------------------------------------
2432 procedure Traverse_Subprogram_Or_Task_Body
2433 (N : Node_Id;
2434 D : Dominant_Info := No_Dominant)
2436 Decls : constant List_Id := Declarations (N);
2437 Dom_Info : Dominant_Info := D;
2438 begin
2439 -- If declarations are present, the first statement is dominated by the
2440 -- last declaration.
2442 Dom_Info := Traverse_Declarations_Or_Statements
2443 (L => Decls, D => Dom_Info);
2445 Traverse_Handled_Statement_Sequence
2446 (N => Handled_Statement_Sequence (N),
2447 D => Dom_Info);
2448 end Traverse_Subprogram_Or_Task_Body;
2450 -------------------------
2451 -- SCO_Record_Filtered --
2452 -------------------------
2454 procedure SCO_Record_Filtered is
2455 type Decision is record
2456 Kind : Character;
2457 -- Type of the SCO decision (see comments for SCO_Table_Entry.C1)
2459 Sloc : Source_Location;
2461 Top : Nat;
2462 -- Index in the SCO_Raw_Table for the root operator/condition for the
2463 -- expression that controls the decision.
2464 end record;
2465 -- Decision descriptor: used to gather information about a candidate
2466 -- SCO decision.
2468 package Pending_Decisions is new Table.Table
2469 (Table_Component_Type => Decision,
2470 Table_Index_Type => Nat,
2471 Table_Low_Bound => 1,
2472 Table_Initial => 1000,
2473 Table_Increment => 200,
2474 Table_Name => "Filter_Pending_Decisions");
2475 -- Table used to hold decisions to process during the collection pass
2477 function Is_Decision (Idx : Nat) return Boolean;
2478 -- Return if the expression tree starting at Idx has adjacent nested
2479 -- nodes that make a decision.
2481 procedure Search_Nested_Decisions (Idx : in out Nat);
2482 -- Collect decisions to add to the filtered SCO table starting at the
2483 -- node at Idx in the SCO raw table. This node must not be part of an
2484 -- already-processed decision. Set Idx to the first node index passed
2485 -- the whole expression tree.
2487 procedure Skip_Decision
2488 (Idx : in out Nat;
2489 Process_Nested_Decisions : Boolean);
2490 -- Skip all the nodes that belong to the decision starting at Idx. If
2491 -- Process_Nested_Decision, call Search_Nested_Decisions on the first
2492 -- nested nodes that do not belong to the decision. Set Idx to the first
2493 -- node index passed the whole expression tree.
2495 procedure Collect_Decisions
2496 (D : Decision;
2497 Next : out Nat);
2498 -- Collect decisions to add to the filtered SCO table starting at the
2499 -- D decision (including it and its nested operators/conditions). Set
2500 -- Next to the first node index passed the whole decision.
2502 procedure Compute_Range
2503 (Idx : in out Nat;
2504 From : out Source_Location;
2505 To : out Source_Location);
2506 -- Compute the source location range for the expression tree starting at
2507 -- Idx in the SCO raw table. Store its bounds in From and To.
2509 procedure Add_Expression_Tree (Idx : in out Nat);
2510 -- Add SCO raw table entries for the decision controlling expression
2511 -- tree starting at Idx to the filtered SCO table.
2513 procedure Process_Pending_Decisions
2514 (Original_Decision : SCO_Table_Entry);
2515 -- Complete the filtered SCO table using collected decisions. Output
2516 -- decisions inherit the pragma information from the original decision.
2518 -----------------
2519 -- Is_Decision --
2520 -----------------
2522 function Is_Decision (Idx : Nat) return Boolean is
2523 Index : Nat := Idx;
2525 begin
2526 loop
2527 declare
2528 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
2530 begin
2531 case T.C1 is
2532 when ' ' =>
2533 return False;
2535 when '!' =>
2537 -- This is a decision iff the only operand of the NOT
2538 -- operator could be a standalone decision.
2540 Index := Idx + 1;
2542 when others =>
2544 -- This node is a logical operator (and thus could be a
2545 -- standalone decision) iff it is a short circuit
2546 -- operator.
2548 return T.C2 /= '?';
2550 end case;
2551 end;
2552 end loop;
2553 end Is_Decision;
2555 -----------------------------
2556 -- Search_Nested_Decisions --
2557 -----------------------------
2559 procedure Search_Nested_Decisions (Idx : in out Nat)
2561 begin
2562 loop
2563 declare
2564 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2566 begin
2567 case T.C1 is
2568 when ' ' =>
2569 Idx := Idx + 1;
2570 exit;
2572 when '!' =>
2573 Collect_Decisions
2574 ((Kind => 'X',
2575 Sloc => T.From,
2576 Top => Idx),
2577 Idx);
2578 exit;
2580 when others =>
2581 if T.C2 = '?' then
2583 -- This in not a logical operator: start looking for
2584 -- nested decisions from here. Recurse over the left
2585 -- child and let the loop take care of the right one.
2587 Idx := Idx + 1;
2588 Search_Nested_Decisions (Idx);
2590 else
2591 -- We found a nested decision
2593 Collect_Decisions
2594 ((Kind => 'X',
2595 Sloc => T.From,
2596 Top => Idx),
2597 Idx);
2598 exit;
2599 end if;
2600 end case;
2601 end;
2602 end loop;
2603 end Search_Nested_Decisions;
2605 -------------------
2606 -- Skip_Decision --
2607 -------------------
2609 procedure Skip_Decision
2610 (Idx : in out Nat;
2611 Process_Nested_Decisions : Boolean)
2613 begin
2614 loop
2615 declare
2616 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2618 begin
2619 Idx := Idx + 1;
2621 case T.C1 is
2622 when ' ' =>
2623 exit;
2625 when '!' =>
2627 -- This NOT operator belongs to the outside decision:
2628 -- just skip it.
2630 null;
2632 when others =>
2633 if T.C2 = '?' and then Process_Nested_Decisions then
2635 -- This in not a logical operator: start looking for
2636 -- nested decisions from here. Recurse over the left
2637 -- child and let the loop take care of the right one.
2639 Search_Nested_Decisions (Idx);
2641 else
2642 -- This is a logical operator, so it belongs to the
2643 -- outside decision: skip its left child, then let the
2644 -- loop take care of the right one.
2646 Skip_Decision (Idx, Process_Nested_Decisions);
2647 end if;
2648 end case;
2649 end;
2650 end loop;
2651 end Skip_Decision;
2653 -----------------------
2654 -- Collect_Decisions --
2655 -----------------------
2657 procedure Collect_Decisions
2658 (D : Decision;
2659 Next : out Nat)
2661 Idx : Nat := D.Top;
2662 begin
2663 if D.Kind /= 'X' or else Is_Decision (D.Top) then
2664 Pending_Decisions.Append (D);
2665 end if;
2667 Skip_Decision (Idx, True);
2668 Next := Idx;
2669 end Collect_Decisions;
2671 -------------------
2672 -- Compute_Range --
2673 -------------------
2675 procedure Compute_Range
2676 (Idx : in out Nat;
2677 From : out Source_Location;
2678 To : out Source_Location)
2680 Sloc_F, Sloc_T : Source_Location := No_Source_Location;
2682 procedure Process_One;
2683 -- Process one node of the tree, and recurse over children. Update
2684 -- Idx during the traversal.
2686 -----------------
2687 -- Process_One --
2688 -----------------
2690 procedure Process_One is
2691 begin
2692 if Sloc_F = No_Source_Location
2693 or else
2694 SCO_Raw_Table.Table (Idx).From < Sloc_F
2695 then
2696 Sloc_F := SCO_Raw_Table.Table (Idx).From;
2697 end if;
2698 if Sloc_T = No_Source_Location
2699 or else
2700 Sloc_T < SCO_Raw_Table.Table (Idx).To
2701 then
2702 Sloc_T := SCO_Raw_Table.Table (Idx).To;
2703 end if;
2705 if SCO_Raw_Table.Table (Idx).C1 = ' ' then
2707 -- This is a condition: nothing special to do
2709 Idx := Idx + 1;
2711 elsif SCO_Raw_Table.Table (Idx).C1 = '!' then
2713 -- The "not" operator has only one operand
2715 Idx := Idx + 1;
2716 Process_One;
2718 else
2719 -- This is an AND THEN or OR ELSE logical operator: follow the
2720 -- left, then the right operands.
2722 Idx := Idx + 1;
2724 Process_One;
2725 Process_One;
2726 end if;
2727 end Process_One;
2729 -- Start of processing for Compute_Range
2731 begin
2732 Process_One;
2733 From := Sloc_F;
2734 To := Sloc_T;
2735 end Compute_Range;
2737 -------------------------
2738 -- Add_Expression_Tree --
2739 -------------------------
2741 procedure Add_Expression_Tree (Idx : in out Nat)
2743 Node_Idx : constant Nat := Idx;
2744 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Node_Idx);
2745 From, To : Source_Location;
2747 begin
2748 case T.C1 is
2749 when ' ' =>
2751 -- This is a single condition. Add an entry for it and move on
2753 SCO_Table.Append (T);
2754 Idx := Idx + 1;
2756 when '!' =>
2758 -- This is a NOT operator: add an entry for it and browse its
2759 -- only child.
2761 SCO_Table.Append (T);
2762 Idx := Idx + 1;
2763 Add_Expression_Tree (Idx);
2765 when others =>
2767 -- This must be an AND/OR/AND THEN/OR ELSE operator
2769 if T.C2 = '?' then
2771 -- This is not a short circuit operator: consider this one
2772 -- and all its children as a single condition.
2774 Compute_Range (Idx, From, To);
2775 SCO_Table.Append
2776 ((From => From,
2777 To => To,
2778 C1 => ' ',
2779 C2 => 'c',
2780 Last => False,
2781 Pragma_Sloc => No_Location,
2782 Pragma_Aspect_Name => No_Name));
2784 else
2785 -- This is a real short circuit operator: add an entry for
2786 -- it and browse its children.
2788 SCO_Table.Append (T);
2789 Idx := Idx + 1;
2790 Add_Expression_Tree (Idx);
2791 Add_Expression_Tree (Idx);
2792 end if;
2793 end case;
2794 end Add_Expression_Tree;
2796 -------------------------------
2797 -- Process_Pending_Decisions --
2798 -------------------------------
2800 procedure Process_Pending_Decisions
2801 (Original_Decision : SCO_Table_Entry)
2803 begin
2804 for Index in 1 .. Pending_Decisions.Last loop
2805 declare
2806 D : Decision renames Pending_Decisions.Table (Index);
2807 Idx : Nat := D.Top;
2809 begin
2810 -- Add a SCO table entry for the decision itself
2812 pragma Assert (D.Kind /= ' ');
2814 SCO_Table.Append
2815 ((To => No_Source_Location,
2816 From => D.Sloc,
2817 C1 => D.Kind,
2818 C2 => ' ',
2819 Last => False,
2820 Pragma_Sloc => Original_Decision.Pragma_Sloc,
2821 Pragma_Aspect_Name =>
2822 Original_Decision.Pragma_Aspect_Name));
2824 -- Then add ones for its nested operators/operands. Do not
2825 -- forget to tag its *last* entry as such.
2827 Add_Expression_Tree (Idx);
2828 SCO_Table.Table (SCO_Table.Last).Last := True;
2829 end;
2830 end loop;
2832 -- Clear the pending decisions list
2833 Pending_Decisions.Set_Last (0);
2834 end Process_Pending_Decisions;
2836 -- Start of processing for SCO_Record_Filtered
2838 begin
2839 -- Filtering must happen only once: do nothing if it this pass was
2840 -- already run.
2842 if SCO_Generation_State = Filtered then
2843 return;
2844 else
2845 pragma Assert (SCO_Generation_State = Raw);
2846 SCO_Generation_State := Filtered;
2847 end if;
2849 -- Loop through all SCO entries under SCO units
2851 for Unit_Idx in 1 .. SCO_Unit_Table.Last loop
2852 declare
2853 Unit : SCO_Unit_Table_Entry
2854 renames SCO_Unit_Table.Table (Unit_Idx);
2856 Idx : Nat := Unit.From;
2857 -- Index of the current SCO raw table entry
2859 New_From : constant Nat := SCO_Table.Last + 1;
2860 -- After copying SCO enties of interest to the final table, we
2861 -- will have to change the From/To indexes this unit targets.
2862 -- This constant keeps track of the new From index.
2864 begin
2865 while Idx <= Unit.To loop
2866 declare
2867 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2869 begin
2870 case T.C1 is
2872 -- Decision (of any kind, including pragmas and aspects)
2874 when 'E' | 'G' | 'I' | 'W' | 'X' | 'P' | 'a' | 'A' =>
2875 if SCO_Pragma_Disabled (T.Pragma_Sloc) then
2877 -- Skip SCO entries for decisions in disabled
2878 -- constructs (pragmas or aspects).
2880 Idx := Idx + 1;
2881 Skip_Decision (Idx, False);
2883 else
2884 Collect_Decisions
2885 ((Kind => T.C1,
2886 Sloc => T.From,
2887 Top => Idx + 1),
2888 Idx);
2889 Process_Pending_Decisions (T);
2890 end if;
2892 -- There is no translation/filtering to do for other kind
2893 -- of SCO items (statements, dominance markers, etc.).
2895 when '|' | '&' | '!' | ' ' =>
2897 -- SCO logical operators and conditions cannot exist
2898 -- on their own: they must be inside a decision (such
2899 -- entries must have been skipped by
2900 -- Collect_Decisions).
2902 raise Program_Error;
2904 when others =>
2905 SCO_Table.Append (T);
2906 Idx := Idx + 1;
2907 end case;
2908 end;
2909 end loop;
2911 -- Now, update the SCO entry indexes in the unit entry
2913 Unit.From := New_From;
2914 Unit.To := SCO_Table.Last;
2915 end;
2916 end loop;
2918 -- Then clear the raw table to free bytes
2920 SCO_Raw_Table.Free;
2921 end SCO_Record_Filtered;
2923 end Par_SCO;