MATCH: Improve `A CMP 0 ? A : -A` set of patterns to use bitwise_equal_p.
[official-gcc.git] / gcc / ada / par_sco.adb
blob5e65fa25de1dc1e89c925e0b16aaa3156c015769
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-2023, 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 Sinfo.Nodes; use Sinfo.Nodes;
42 with Sinfo.Utils; use Sinfo.Utils;
43 with Sinput; use Sinput;
44 with Snames; use Snames;
45 with Table;
47 with GNAT.HTable; use GNAT.HTable;
48 with GNAT.Heap_Sort_G;
50 package body Par_SCO is
52 --------------------------
53 -- First-pass SCO table --
54 --------------------------
56 -- The Short_Circuit_And_Or pragma enables one to use AND and OR operators
57 -- in source code while the ones used with booleans will be interpreted as
58 -- their short circuit alternatives (AND THEN and OR ELSE). Thus, the true
59 -- meaning of these operators is known only after the semantic analysis.
61 -- However, decision SCOs include short circuit operators only. The SCO
62 -- information generation pass must be done before expansion, hence before
63 -- the semantic analysis. Because of this, the SCO information generation
64 -- is done in two passes.
66 -- The first one (SCO_Record_Raw, before semantic analysis) completes the
67 -- SCO_Raw_Table assuming all AND/OR operators are short circuit ones.
68 -- Then, the semantic analysis determines which operators are promoted to
69 -- short circuit ones. Finally, the second pass (SCO_Record_Filtered)
70 -- translates the SCO_Raw_Table to SCO_Table, taking care of removing the
71 -- remaining AND/OR operators and of adjusting decisions accordingly
72 -- (splitting decisions, removing empty ones, etc.).
74 type SCO_Generation_State_Type is (None, Raw, Filtered);
75 SCO_Generation_State : SCO_Generation_State_Type := None;
76 -- Keep track of the SCO generation state: this will prevent us from
77 -- running some steps multiple times (the second pass has to be started
78 -- from multiple places).
80 package SCO_Raw_Table is new Table.Table
81 (Table_Component_Type => SCO_Table_Entry,
82 Table_Index_Type => Nat,
83 Table_Low_Bound => 1,
84 Table_Initial => 500,
85 Table_Increment => 300,
86 Table_Name => "Raw_Table");
88 -----------------------
89 -- Unit Number Table --
90 -----------------------
92 -- This table parallels the SCO_Unit_Table, keeping track of the unit
93 -- numbers corresponding to the entries made in this table, so that before
94 -- writing out the SCO information to the ALI file, we can fill in the
95 -- proper dependency numbers and file names.
97 -- Note that the zeroth entry is here for convenience in sorting the table;
98 -- the real lower bound is 1.
100 package SCO_Unit_Number_Table is new Table.Table
101 (Table_Component_Type => Unit_Number_Type,
102 Table_Index_Type => SCO_Unit_Index,
103 Table_Low_Bound => 0, -- see note above on sort
104 Table_Initial => 20,
105 Table_Increment => 200,
106 Table_Name => "SCO_Unit_Number_Entry");
108 ------------------------------------------
109 -- Condition/Operator/Pragma Hash Table --
110 ------------------------------------------
112 -- We need to be able to get to conditions quickly for handling the calls
113 -- to Set_SCO_Condition efficiently, and similarly to get to pragmas to
114 -- handle calls to Set_SCO_Pragma_Enabled (the same holds for operators and
115 -- Set_SCO_Logical_Operator). For this purpose we identify the conditions,
116 -- operators and pragmas in the table by their starting sloc, and use this
117 -- hash table to map from these sloc values to SCO_Table indexes.
119 type Header_Num is new Integer range 0 .. 996;
120 -- Type for hash table headers
122 function Hash (F : Source_Ptr) return Header_Num;
123 -- Function to Hash source pointer value
125 function Equal (F1 : Source_Ptr; F2 : Source_Ptr) return Boolean;
126 -- Function to test two keys for equality
128 function "<" (S1 : Source_Location; S2 : Source_Location) return Boolean;
129 -- Function to test for source locations order
131 package SCO_Raw_Hash_Table is new Simple_HTable
132 (Header_Num, Int, 0, Source_Ptr, Hash, Equal);
133 -- The actual hash table
135 --------------------------
136 -- Internal Subprograms --
137 --------------------------
139 function Has_Decision (N : Node_Id) return Boolean;
140 -- N is the node for a subexpression. Returns True if the subexpression
141 -- contains a nested decision (i.e. either is a logical operator, or
142 -- contains a logical operator in its subtree).
144 -- This must be used in the first pass (SCO_Record_Raw) only: here AND/OR
145 -- operators are considered as short circuit, just in case the
146 -- Short_Circuit_And_Or pragma is used: only real short circuit operations
147 -- will be kept in the secord pass.
149 type Tristate is (False, True, Unknown);
151 function Is_Logical_Operator (N : Node_Id) return Tristate;
152 -- N is the node for a subexpression. This procedure determines whether N
153 -- is a logical operator: True for short circuit conditions, Unknown for OR
154 -- and AND (the Short_Circuit_And_Or pragma may be used) and False
155 -- otherwise. Note that in cases where True is returned, callers assume
156 -- Nkind (N) in N_Op.
158 function To_Source_Location (S : Source_Ptr) return Source_Location;
159 -- Converts Source_Ptr value to Source_Location (line/col) format
161 procedure Process_Decisions
162 (N : Node_Id;
163 T : Character;
164 Pragma_Sloc : Source_Ptr);
165 -- If N is Empty, has no effect. Otherwise scans the tree for the node N,
166 -- to output any decisions it contains. T is one of IEGPWX (for context of
167 -- expression: if/exit when/entry guard/pragma/while/expression). If T is
168 -- other than X, the node N is the if expression involved, and a decision
169 -- is always present (at the very least a simple decision is present at the
170 -- top level).
172 procedure Process_Decisions
173 (L : List_Id;
174 T : Character;
175 Pragma_Sloc : Source_Ptr);
176 -- Calls above procedure for each element of the list L
178 procedure Set_Raw_Table_Entry
179 (C1 : Character;
180 C2 : Character;
181 From : Source_Ptr;
182 To : Source_Ptr;
183 Last : Boolean;
184 Pragma_Sloc : Source_Ptr := No_Location;
185 Pragma_Aspect_Name : Name_Id := No_Name);
186 -- Append an entry to SCO_Raw_Table with fields set as per arguments
188 type Dominant_Info is record
189 K : Character;
190 -- F/T/S/E for a valid dominance marker, or ' ' for no dominant
192 N : Node_Id;
193 -- Node providing the Sloc(s) for the dominance marker
194 end record;
195 No_Dominant : constant Dominant_Info := (' ', Empty);
197 procedure Record_Instance (Id : Instance_Id; Inst_Sloc : Source_Ptr);
198 -- Add one entry from the instance table to the corresponding SCO table
200 procedure Traverse_Declarations_Or_Statements
201 (L : List_Id;
202 D : Dominant_Info := No_Dominant;
203 P : Node_Id := Empty);
204 -- Process L, a list of statements or declarations dominated by D. If P is
205 -- present, it is processed as though it had been prepended to L.
207 function Traverse_Declarations_Or_Statements
208 (L : List_Id;
209 D : Dominant_Info := No_Dominant;
210 P : Node_Id := Empty) return Dominant_Info;
211 -- Same as above, and returns dominant information corresponding to the
212 -- last node with SCO in L.
214 -- The following Traverse_* routines perform appropriate calls to
215 -- Traverse_Declarations_Or_Statements to traverse specific node kinds.
216 -- Parameter D, when present, indicates the dominant of the first
217 -- declaration or statement within N.
219 procedure Traverse_Generic_Package_Declaration (N : Node_Id);
221 procedure Traverse_Handled_Statement_Sequence
222 (N : Node_Id;
223 D : Dominant_Info := No_Dominant);
225 procedure Traverse_Package_Body (N : Node_Id);
227 procedure Traverse_Package_Declaration
228 (N : Node_Id;
229 D : Dominant_Info := No_Dominant);
231 procedure Traverse_Subprogram_Or_Task_Body
232 (N : Node_Id;
233 D : Dominant_Info := No_Dominant);
235 procedure Traverse_Protected_Or_Task_Definition (N : Node_Id);
237 -- Note regarding traversals: In a few cases where an Alternatives list is
238 -- involved, pragmas such as "pragma Page" may show up before the first
239 -- alternative. We skip them because we're out of statement or declaration
240 -- context, so these can't be pragmas of interest for SCO purposes, and
241 -- the regular alternative processing typically involves attribute queries
242 -- which aren't valid for a pragma.
244 procedure Write_SCOs_To_ALI_File is new Put_SCOs;
245 -- Write SCO information to the ALI file using routines in Lib.Util
247 ----------
248 -- dsco --
249 ----------
251 procedure dsco is
252 procedure Dump_Entry (Index : Nat; T : SCO_Table_Entry);
253 -- Dump a SCO table entry
255 ----------------
256 -- Dump_Entry --
257 ----------------
259 procedure Dump_Entry (Index : Nat; T : SCO_Table_Entry) is
260 begin
261 Write_Str (" ");
262 Write_Int (Index);
263 Write_Char ('.');
265 if T.C1 /= ' ' then
266 Write_Str (" C1 = '");
267 Write_Char (T.C1);
268 Write_Char (''');
269 end if;
271 if T.C2 /= ' ' then
272 Write_Str (" C2 = '");
273 Write_Char (T.C2);
274 Write_Char (''');
275 end if;
277 if T.From /= No_Source_Location then
278 Write_Str (" From = ");
279 Write_Int (Int (T.From.Line));
280 Write_Char (':');
281 Write_Int (Int (T.From.Col));
282 end if;
284 if T.To /= No_Source_Location then
285 Write_Str (" To = ");
286 Write_Int (Int (T.To.Line));
287 Write_Char (':');
288 Write_Int (Int (T.To.Col));
289 end if;
291 if T.Last then
292 Write_Str (" True");
293 else
294 Write_Str (" False");
295 end if;
297 Write_Eol;
298 end Dump_Entry;
300 -- Start of processing for dsco
302 begin
303 -- Dump SCO unit table
305 Write_Line ("SCO Unit Table");
306 Write_Line ("--------------");
308 for Index in 1 .. SCO_Unit_Table.Last loop
309 declare
310 UTE : SCO_Unit_Table_Entry renames SCO_Unit_Table.Table (Index);
312 begin
313 Write_Str (" ");
314 Write_Int (Int (Index));
315 Write_Str (" Dep_Num = ");
316 Write_Int (Int (UTE.Dep_Num));
317 Write_Str (" From = ");
318 Write_Int (Int (UTE.From));
319 Write_Str (" To = ");
320 Write_Int (Int (UTE.To));
322 Write_Str (" File_Name = """);
324 if UTE.File_Name /= null then
325 Write_Str (UTE.File_Name.all);
326 end if;
328 Write_Char ('"');
329 Write_Eol;
330 end;
331 end loop;
333 -- Dump SCO Unit number table if it contains any entries
335 if SCO_Unit_Number_Table.Last >= 1 then
336 Write_Eol;
337 Write_Line ("SCO Unit Number Table");
338 Write_Line ("---------------------");
340 for Index in 1 .. SCO_Unit_Number_Table.Last loop
341 Write_Str (" ");
342 Write_Int (Int (Index));
343 Write_Str (". Unit_Number = ");
344 Write_Int (Int (SCO_Unit_Number_Table.Table (Index)));
345 Write_Eol;
346 end loop;
347 end if;
349 -- Dump SCO raw-table
351 Write_Eol;
352 Write_Line ("SCO Raw Table");
353 Write_Line ("---------");
355 if SCO_Generation_State = Filtered then
356 Write_Line ("Empty (free'd after second pass)");
357 else
358 for Index in 1 .. SCO_Raw_Table.Last loop
359 Dump_Entry (Index, SCO_Raw_Table.Table (Index));
360 end loop;
361 end if;
363 -- Dump SCO table itself
365 Write_Eol;
366 Write_Line ("SCO Filtered Table");
367 Write_Line ("---------");
369 for Index in 1 .. SCO_Table.Last loop
370 Dump_Entry (Index, SCO_Table.Table (Index));
371 end loop;
372 end dsco;
374 -----------
375 -- Equal --
376 -----------
378 function Equal (F1 : Source_Ptr; F2 : Source_Ptr) return Boolean is
379 begin
380 return F1 = F2;
381 end Equal;
383 -------
384 -- < --
385 -------
387 function "<" (S1 : Source_Location; S2 : Source_Location) return Boolean is
388 begin
389 return S1.Line < S2.Line
390 or else (S1.Line = S2.Line and then S1.Col < S2.Col);
391 end "<";
393 ------------------
394 -- Has_Decision --
395 ------------------
397 function Has_Decision (N : Node_Id) return Boolean is
398 function Check_Node (N : Node_Id) return Traverse_Result;
399 -- Determine if Nkind (N) indicates the presence of a decision (i.e. N
400 -- is a logical operator, which is a decision in itself, or an
401 -- IF-expression whose Condition attribute is a decision, or a
402 -- quantified expression, whose predicate is a decision).
404 ----------------
405 -- Check_Node --
406 ----------------
408 function Check_Node (N : Node_Id) return Traverse_Result is
409 begin
410 -- If we are not sure this is a logical operator (AND and OR may be
411 -- turned into logical operators with the Short_Circuit_And_Or
412 -- pragma), assume it is. Putative decisions will be discarded if
413 -- needed in the second pass.
415 if Is_Logical_Operator (N) /= False
416 or else Nkind (N) = N_If_Expression
417 or else Nkind (N) = N_Quantified_Expression
418 then
419 return Abandon;
420 else
421 return OK;
422 end if;
423 end Check_Node;
425 function Traverse is new Traverse_Func (Check_Node);
427 -- Start of processing for Has_Decision
429 begin
430 return Traverse (N) = Abandon;
431 end Has_Decision;
433 ----------
434 -- Hash --
435 ----------
437 function Hash (F : Source_Ptr) return Header_Num is
438 begin
439 return Header_Num (Nat (F) mod 997);
440 end Hash;
442 ----------------
443 -- Initialize --
444 ----------------
446 procedure Initialize is
447 begin
448 SCO_Unit_Number_Table.Init;
450 -- The SCO_Unit_Number_Table entry with index 0 is intentionally set
451 -- aside to be used as temporary for sorting.
453 SCO_Unit_Number_Table.Increment_Last;
454 end Initialize;
456 -------------------------
457 -- Is_Logical_Operator --
458 -------------------------
460 function Is_Logical_Operator (N : Node_Id) return Tristate is
461 begin
462 if Nkind (N) in N_And_Then | N_Op_Not | N_Or_Else then
463 return True;
464 elsif Nkind (N) in N_Op_And | N_Op_Or then
465 return Unknown;
466 else
467 return False;
468 end if;
469 end Is_Logical_Operator;
471 -----------------------
472 -- Process_Decisions --
473 -----------------------
475 -- Version taking a list
477 procedure Process_Decisions
478 (L : List_Id;
479 T : Character;
480 Pragma_Sloc : Source_Ptr)
482 N : Node_Id;
484 begin
485 N := First (L);
486 while Present (N) loop
487 Process_Decisions (N, T, Pragma_Sloc);
488 Next (N);
489 end loop;
490 end Process_Decisions;
492 -- Version taking a node
494 Current_Pragma_Sloc : Source_Ptr := No_Location;
495 -- While processing a pragma, this is set to the sloc of the N_Pragma node
497 procedure Process_Decisions
498 (N : Node_Id;
499 T : Character;
500 Pragma_Sloc : Source_Ptr)
502 Mark : Nat;
503 -- This is used to mark the location of a decision sequence in the SCO
504 -- table. We use it for backing out a simple decision in an expression
505 -- context that contains only NOT operators.
507 Mark_Hash : Nat;
508 -- Likewise for the putative SCO_Raw_Hash_Table entries: see below
510 type Hash_Entry is record
511 Sloc : Source_Ptr;
512 SCO_Index : Nat;
513 end record;
514 -- We must register all conditions/pragmas in SCO_Raw_Hash_Table.
515 -- However we cannot register them in the same time we are adding the
516 -- corresponding SCO entries to the raw table since we may discard them
517 -- later on. So instead we put all putative conditions into Hash_Entries
518 -- (see below) and register them once we are sure we keep them.
520 -- This data structure holds the conditions/pragmas to register in
521 -- SCO_Raw_Hash_Table.
523 package Hash_Entries is new Table.Table
524 (Table_Component_Type => Hash_Entry,
525 Table_Index_Type => Nat,
526 Table_Low_Bound => 1,
527 Table_Initial => 10,
528 Table_Increment => 10,
529 Table_Name => "Hash_Entries");
530 -- Hold temporarily (i.e. free'd before returning) the Hash_Entry before
531 -- they are registered in SCO_Raw_Hash_Table.
533 X_Not_Decision : Boolean;
534 -- This flag keeps track of whether a decision sequence in the SCO table
535 -- contains only NOT operators, and is for an expression context (T=X).
536 -- The flag will be set False if T is other than X, or if an operator
537 -- other than NOT is in the sequence.
539 procedure Output_Decision_Operand (N : Node_Id);
540 -- The node N is the top level logical operator of a decision, or it is
541 -- one of the operands of a logical operator belonging to a single
542 -- complex decision. This routine outputs the sequence of table entries
543 -- corresponding to the node. Note that we do not process the sub-
544 -- operands to look for further decisions, that processing is done in
545 -- Process_Decision_Operand, because we can't get decisions mixed up in
546 -- the global table. Call has no effect if N is Empty.
548 procedure Output_Element (N : Node_Id);
549 -- Node N is an operand of a logical operator that is not itself a
550 -- logical operator, or it is a simple decision. This routine outputs
551 -- the table entry for the element, with C1 set to ' '. Last is set
552 -- False, and an entry is made in the condition hash table.
554 procedure Output_Header (T : Character);
555 -- Outputs a decision header node. T is I/W/E/P for IF/WHILE/EXIT WHEN/
556 -- PRAGMA, and 'X' for the expression case.
558 procedure Process_Decision_Operand (N : Node_Id);
559 -- This is called on node N, the top level node of a decision, or on one
560 -- of its operands or suboperands after generating the full output for
561 -- the complex decision. It process the suboperands of the decision
562 -- looking for nested decisions.
564 function Process_Node (N : Node_Id) return Traverse_Result;
565 -- Processes one node in the traversal, looking for logical operators,
566 -- and if one is found, outputs the appropriate table entries.
568 -----------------------------
569 -- Output_Decision_Operand --
570 -----------------------------
572 procedure Output_Decision_Operand (N : Node_Id) is
573 C1 : Character;
574 C2 : Character;
575 -- C1 holds a character that identifies the operation while C2
576 -- indicates whether we are sure (' ') or not ('?') this operation
577 -- belongs to the decision. '?' entries will be filtered out in the
578 -- second (SCO_Record_Filtered) pass.
580 L : Node_Id;
581 T : Tristate;
583 begin
584 if No (N) then
585 return;
586 end if;
588 T := Is_Logical_Operator (N);
590 -- Logical operator
592 if T /= False then
593 if Nkind (N) = N_Op_Not then
594 C1 := '!';
595 L := Empty;
597 else
598 L := Left_Opnd (N);
600 if Nkind (N) in N_Op_Or | N_Or_Else then
601 C1 := '|';
602 else pragma Assert (Nkind (N) in N_Op_And | N_And_Then);
603 C1 := '&';
604 end if;
605 end if;
607 if T = True then
608 C2 := ' ';
609 else
610 C2 := '?';
611 end if;
613 Set_Raw_Table_Entry
614 (C1 => C1,
615 C2 => C2,
616 From => Sloc (N),
617 To => No_Location,
618 Last => False);
620 Hash_Entries.Append ((Sloc (N), SCO_Raw_Table.Last));
622 Output_Decision_Operand (L);
623 Output_Decision_Operand (Right_Opnd (N));
625 -- Not a logical operator
627 else
628 Output_Element (N);
629 end if;
630 end Output_Decision_Operand;
632 --------------------
633 -- Output_Element --
634 --------------------
636 procedure Output_Element (N : Node_Id) is
637 FSloc : Source_Ptr;
638 LSloc : Source_Ptr;
639 begin
640 Sloc_Range (N, FSloc, LSloc);
641 Set_Raw_Table_Entry
642 (C1 => ' ',
643 C2 => 'c',
644 From => FSloc,
645 To => LSloc,
646 Last => False);
647 Hash_Entries.Append ((FSloc, SCO_Raw_Table.Last));
648 end Output_Element;
650 -------------------
651 -- Output_Header --
652 -------------------
654 procedure Output_Header (T : Character) is
655 Loc : Source_Ptr := No_Location;
656 -- Node whose Sloc is used for the decision
658 Nam : Name_Id := No_Name;
659 -- For the case of an aspect, aspect name
661 begin
662 case T is
663 when 'I' | 'E' | 'W' | 'a' | 'A' =>
665 -- For IF, EXIT, WHILE, or aspects, the token SLOC is that of
666 -- the parent of the expression.
668 Loc := Sloc (Parent (N));
670 if T = 'a' or else T = 'A' then
671 Nam := Chars (Identifier (Parent (N)));
672 end if;
674 when 'G' | 'P' =>
676 -- For entry guard, the token sloc is from the N_Entry_Body.
677 -- For PRAGMA, we must get the location from the pragma node.
678 -- Argument N is the pragma argument, and we have to go up
679 -- two levels (through the pragma argument association) to
680 -- get to the pragma node itself. For the guard on a select
681 -- alternative, we do not have access to the token location for
682 -- the WHEN, so we use the first sloc of the condition itself.
683 -- First_Sloc gives the most sensible result, but we have to
684 -- beware of also using it when computing the dominance marker
685 -- sloc (in the Set_Statement_Entry procedure), as this is not
686 -- fully equivalent to the "To" sloc computed by
687 -- Sloc_Range (Guard, To, From).
689 if Nkind (Parent (N)) in N_Accept_Alternative
690 | N_Delay_Alternative
691 | N_Terminate_Alternative
692 then
693 Loc := First_Sloc (N);
694 else
695 Loc := Sloc (Parent (Parent (N)));
696 end if;
698 when 'X' =>
700 -- For an expression, no Sloc
702 null;
704 -- No other possibilities
706 when others =>
707 raise Program_Error;
708 end case;
710 Set_Raw_Table_Entry
711 (C1 => T,
712 C2 => ' ',
713 From => Loc,
714 To => No_Location,
715 Last => False,
716 Pragma_Sloc => Pragma_Sloc,
717 Pragma_Aspect_Name => Nam);
719 -- For an aspect specification, which will be rewritten into a
720 -- pragma, enter a hash table entry now.
722 if T = 'a' then
723 Hash_Entries.Append ((Loc, SCO_Raw_Table.Last));
724 end if;
725 end Output_Header;
727 ------------------------------
728 -- Process_Decision_Operand --
729 ------------------------------
731 procedure Process_Decision_Operand (N : Node_Id) is
732 begin
733 if Is_Logical_Operator (N) /= False then
734 if Nkind (N) /= N_Op_Not then
735 Process_Decision_Operand (Left_Opnd (N));
736 X_Not_Decision := False;
737 end if;
739 Process_Decision_Operand (Right_Opnd (N));
741 else
742 Process_Decisions (N, 'X', Pragma_Sloc);
743 end if;
744 end Process_Decision_Operand;
746 ------------------
747 -- Process_Node --
748 ------------------
750 function Process_Node (N : Node_Id) return Traverse_Result is
751 begin
752 case Nkind (N) is
754 -- Logical operators, output table entries and then process
755 -- operands recursively to deal with nested conditions.
757 when N_And_Then
758 | N_Op_And
759 | N_Op_Not
760 | N_Op_Or
761 | N_Or_Else
763 declare
764 T : Character;
766 begin
767 -- If outer level, then type comes from call, otherwise it
768 -- is more deeply nested and counts as X for expression.
770 if N = Process_Decisions.N then
771 T := Process_Decisions.T;
772 else
773 T := 'X';
774 end if;
776 -- Output header for sequence
778 X_Not_Decision := T = 'X' and then Nkind (N) = N_Op_Not;
779 Mark := SCO_Raw_Table.Last;
780 Mark_Hash := Hash_Entries.Last;
781 Output_Header (T);
783 -- Output the decision
785 Output_Decision_Operand (N);
787 -- If the decision was in an expression context (T = 'X')
788 -- and contained only NOT operators, then we don't output
789 -- it, so delete it.
791 if X_Not_Decision then
792 SCO_Raw_Table.Set_Last (Mark);
793 Hash_Entries.Set_Last (Mark_Hash);
795 -- Otherwise, set Last in last table entry to mark end
797 else
798 SCO_Raw_Table.Table (SCO_Raw_Table.Last).Last := True;
799 end if;
801 -- Process any embedded decisions
803 Process_Decision_Operand (N);
804 return Skip;
805 end;
807 -- Case expression
809 -- Really hard to believe this is correct given the special
810 -- handling for if expressions below ???
812 when N_Case_Expression =>
813 return OK; -- ???
815 -- If expression, processed like an if statement
817 when N_If_Expression =>
818 declare
819 Cond : constant Node_Id := First (Expressions (N));
820 Thnx : constant Node_Id := Next (Cond);
821 Elsx : constant Node_Id := Next (Thnx);
823 begin
824 Process_Decisions (Cond, 'I', Pragma_Sloc);
825 Process_Decisions (Thnx, 'X', Pragma_Sloc);
826 Process_Decisions (Elsx, 'X', Pragma_Sloc);
827 return Skip;
828 end;
830 when N_Quantified_Expression =>
831 declare
832 Cond : constant Node_Id := Condition (N);
833 I_Spec : Node_Id := Empty;
834 begin
835 if Present (Iterator_Specification (N)) then
836 I_Spec := Iterator_Specification (N);
837 else
838 I_Spec := Loop_Parameter_Specification (N);
839 end if;
840 Process_Decisions (I_Spec, 'X', Pragma_Sloc);
841 Process_Decisions (Cond, 'W', Pragma_Sloc);
842 return Skip;
843 end;
845 -- All other cases, continue scan
847 when others =>
848 return OK;
849 end case;
850 end Process_Node;
852 procedure Traverse is new Traverse_Proc (Process_Node);
854 -- Start of processing for Process_Decisions
856 begin
857 if No (N) then
858 return;
859 end if;
861 Hash_Entries.Init;
863 -- See if we have simple decision at outer level and if so then
864 -- generate the decision entry for this simple decision. A simple
865 -- decision is a boolean expression (which is not a logical operator
866 -- or short circuit form) appearing as the operand of an IF, WHILE,
867 -- EXIT WHEN, or special PRAGMA construct.
869 if T /= 'X' and then Is_Logical_Operator (N) = False then
870 Output_Header (T);
871 Output_Element (N);
873 -- Change Last in last table entry to True to mark end of
874 -- sequence, which is this case is only one element long.
876 SCO_Raw_Table.Table (SCO_Raw_Table.Last).Last := True;
877 end if;
879 Traverse (N);
881 -- Now we have the definitive set of SCO entries, register them in the
882 -- corresponding hash table.
884 for J in 1 .. Hash_Entries.Last loop
885 SCO_Raw_Hash_Table.Set
886 (Hash_Entries.Table (J).Sloc,
887 Hash_Entries.Table (J).SCO_Index);
888 end loop;
890 Hash_Entries.Free;
891 end Process_Decisions;
893 -----------
894 -- pscos --
895 -----------
897 procedure pscos is
898 procedure Write_Info_Char (C : Character) renames Write_Char;
899 -- Write one character;
901 procedure Write_Info_Initiate (Key : Character) renames Write_Char;
902 -- Start new one and write one character;
904 procedure Write_Info_Nat (N : Nat);
905 -- Write value of N
907 procedure Write_Info_Terminate renames Write_Eol;
908 -- Terminate current line
910 --------------------
911 -- Write_Info_Nat --
912 --------------------
914 procedure Write_Info_Nat (N : Nat) is
915 begin
916 Write_Int (N);
917 end Write_Info_Nat;
919 procedure Debug_Put_SCOs is new Put_SCOs;
921 -- Start of processing for pscos
923 begin
924 Debug_Put_SCOs;
925 end pscos;
927 ---------------------
928 -- Record_Instance --
929 ---------------------
931 procedure Record_Instance (Id : Instance_Id; Inst_Sloc : Source_Ptr) is
932 Inst_Src : constant Source_File_Index :=
933 Get_Source_File_Index (Inst_Sloc);
934 begin
935 SCO_Instance_Table.Append
936 ((Inst_Dep_Num => Dependency_Num (Unit (Inst_Src)),
937 Inst_Loc => To_Source_Location (Inst_Sloc),
938 Enclosing_Instance => SCO_Instance_Index (Instance (Inst_Src))));
940 pragma Assert
941 (SCO_Instance_Table.Last = SCO_Instance_Index (Id));
942 end Record_Instance;
944 ----------------
945 -- SCO_Output --
946 ----------------
948 procedure SCO_Output is
949 procedure Populate_SCO_Instance_Table is
950 new Sinput.Iterate_On_Instances (Record_Instance);
952 begin
953 pragma Assert (SCO_Generation_State = Filtered);
955 if Debug_Flag_Dot_OO then
956 dsco;
957 end if;
959 Populate_SCO_Instance_Table;
961 -- Sort the unit tables based on dependency numbers
963 Unit_Table_Sort : declare
964 function Lt (Op1 : Natural; Op2 : Natural) return Boolean;
965 -- Comparison routine for sort call
967 procedure Move (From : Natural; To : Natural);
968 -- Move routine for sort call
970 --------
971 -- Lt --
972 --------
974 function Lt (Op1 : Natural; Op2 : Natural) return Boolean is
975 begin
976 return
977 Dependency_Num
978 (SCO_Unit_Number_Table.Table (SCO_Unit_Index (Op1)))
980 Dependency_Num
981 (SCO_Unit_Number_Table.Table (SCO_Unit_Index (Op2)));
982 end Lt;
984 ----------
985 -- Move --
986 ----------
988 procedure Move (From : Natural; To : Natural) is
989 begin
990 SCO_Unit_Table.Table (SCO_Unit_Index (To)) :=
991 SCO_Unit_Table.Table (SCO_Unit_Index (From));
992 SCO_Unit_Number_Table.Table (SCO_Unit_Index (To)) :=
993 SCO_Unit_Number_Table.Table (SCO_Unit_Index (From));
994 end Move;
996 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
998 -- Start of processing for Unit_Table_Sort
1000 begin
1001 Sorting.Sort (Integer (SCO_Unit_Table.Last));
1002 end Unit_Table_Sort;
1004 -- Loop through entries in the unit table to set file name and
1005 -- dependency number entries.
1007 for J in 1 .. SCO_Unit_Table.Last loop
1008 declare
1009 U : constant Unit_Number_Type := SCO_Unit_Number_Table.Table (J);
1010 UTE : SCO_Unit_Table_Entry renames SCO_Unit_Table.Table (J);
1012 begin
1013 Get_Name_String (Reference_Name (Source_Index (U)));
1014 UTE.File_Name := new String'(Name_Buffer (1 .. Name_Len));
1015 UTE.Dep_Num := Dependency_Num (U);
1016 end;
1017 end loop;
1019 -- Now the tables are all setup for output to the ALI file
1021 Write_SCOs_To_ALI_File;
1022 end SCO_Output;
1024 -------------------------
1025 -- SCO_Pragma_Disabled --
1026 -------------------------
1028 function SCO_Pragma_Disabled (Loc : Source_Ptr) return Boolean is
1029 Index : Nat;
1031 begin
1032 if Loc = No_Location then
1033 return False;
1034 end if;
1036 Index := SCO_Raw_Hash_Table.Get (Loc);
1038 -- The test here for zero is to deal with possible previous errors, and
1039 -- for the case of pragma statement SCOs, for which we always set the
1040 -- Pragma_Sloc even if the particular pragma cannot be specifically
1041 -- disabled.
1043 if Index /= 0 then
1044 declare
1045 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1047 begin
1048 case T.C1 is
1049 when 'S' =>
1050 -- Pragma statement
1052 return T.C2 = 'p';
1054 when 'A' =>
1055 -- Aspect decision (enabled)
1057 return False;
1059 when 'a' =>
1060 -- Aspect decision (not enabled)
1062 return True;
1064 when ASCII.NUL =>
1065 -- Nullified disabled SCO
1067 return True;
1069 when others =>
1070 raise Program_Error;
1071 end case;
1072 end;
1074 else
1075 return False;
1076 end if;
1077 end SCO_Pragma_Disabled;
1079 --------------------
1080 -- SCO_Record_Raw --
1081 --------------------
1083 procedure SCO_Record_Raw (U : Unit_Number_Type) is
1084 procedure Traverse_Aux_Decls (N : Node_Id);
1085 -- Traverse the Aux_Decls_Node of compilation unit N
1087 ------------------------
1088 -- Traverse_Aux_Decls --
1089 ------------------------
1091 procedure Traverse_Aux_Decls (N : Node_Id) is
1092 ADN : constant Node_Id := Aux_Decls_Node (N);
1094 begin
1095 Traverse_Declarations_Or_Statements (Config_Pragmas (ADN));
1096 Traverse_Declarations_Or_Statements (Pragmas_After (ADN));
1098 -- Declarations and Actions do not correspond to source constructs,
1099 -- they contain only nodes from expansion, so at this point they
1100 -- should still be empty:
1102 pragma Assert (No (Declarations (ADN)));
1103 pragma Assert (No (Actions (ADN)));
1104 end Traverse_Aux_Decls;
1106 -- Local variables
1108 From : Nat;
1109 Lu : Node_Id;
1111 -- Start of processing for SCO_Record_Raw
1113 begin
1114 -- It is legitimate to run this pass multiple times (once per unit) so
1115 -- run it even if it was already run before.
1117 pragma Assert (SCO_Generation_State in None .. Raw);
1118 SCO_Generation_State := Raw;
1120 -- Ignore call if not generating code and generating SCO's
1122 if not (Generate_SCO and then Operating_Mode = Generate_Code) then
1123 return;
1124 end if;
1126 -- Ignore call if this unit already recorded
1128 for J in 1 .. SCO_Unit_Number_Table.Last loop
1129 if U = SCO_Unit_Number_Table.Table (J) then
1130 return;
1131 end if;
1132 end loop;
1134 -- Otherwise record starting entry
1136 From := SCO_Raw_Table.Last + 1;
1138 -- Get Unit (checking case of subunit)
1140 Lu := Unit (Cunit (U));
1142 if Nkind (Lu) = N_Subunit then
1143 Lu := Proper_Body (Lu);
1144 end if;
1146 -- Traverse the unit
1148 Traverse_Aux_Decls (Cunit (U));
1150 case Nkind (Lu) is
1151 when N_Generic_Instantiation
1152 | N_Generic_Package_Declaration
1153 | N_Package_Body
1154 | N_Package_Declaration
1155 | N_Protected_Body
1156 | N_Subprogram_Body
1157 | N_Subprogram_Declaration
1158 | N_Task_Body
1160 Traverse_Declarations_Or_Statements (L => No_List, P => Lu);
1162 -- All other cases of compilation units (e.g. renamings), generate no
1163 -- SCO information.
1165 when others =>
1166 null;
1167 end case;
1169 -- Make entry for new unit in unit tables, we will fill in the file
1170 -- name and dependency numbers later.
1172 SCO_Unit_Table.Append (
1173 (Dep_Num => 0,
1174 File_Name => null,
1175 File_Index => Get_Source_File_Index (Sloc (Lu)),
1176 From => From,
1177 To => SCO_Raw_Table.Last));
1179 SCO_Unit_Number_Table.Append (U);
1180 end SCO_Record_Raw;
1182 -----------------------
1183 -- Set_SCO_Condition --
1184 -----------------------
1186 procedure Set_SCO_Condition (Cond : Node_Id; Val : Boolean) is
1188 -- SCO annotations are not processed after the filtering pass
1190 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1192 Constant_Condition_Code : constant array (Boolean) of Character :=
1193 (False => 'f', True => 't');
1195 Orig : constant Node_Id := Original_Node (Cond);
1196 Dummy : Source_Ptr;
1197 Index : Nat;
1198 Start : Source_Ptr;
1200 begin
1201 Sloc_Range (Orig, Start, Dummy);
1202 Index := SCO_Raw_Hash_Table.Get (Start);
1204 -- Index can be zero for boolean expressions that do not have SCOs
1205 -- (simple decisions outside of a control flow structure), or in case
1206 -- of a previous error.
1208 if Index = 0 then
1209 return;
1211 else
1212 pragma Assert (SCO_Raw_Table.Table (Index).C1 = ' ');
1213 SCO_Raw_Table.Table (Index).C2 := Constant_Condition_Code (Val);
1214 end if;
1215 end Set_SCO_Condition;
1217 ------------------------------
1218 -- Set_SCO_Logical_Operator --
1219 ------------------------------
1221 procedure Set_SCO_Logical_Operator (Op : Node_Id) is
1223 -- SCO annotations are not processed after the filtering pass
1225 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1227 Orig : constant Node_Id := Original_Node (Op);
1228 Orig_Sloc : constant Source_Ptr := Sloc (Orig);
1229 Index : constant Nat := SCO_Raw_Hash_Table.Get (Orig_Sloc);
1231 begin
1232 -- All (putative) logical operators are supposed to have their own entry
1233 -- in the SCOs table. However, the semantic analysis may invoke this
1234 -- subprogram with nodes that are out of the SCO generation scope.
1236 if Index /= 0 then
1237 SCO_Raw_Table.Table (Index).C2 := ' ';
1238 end if;
1239 end Set_SCO_Logical_Operator;
1241 ----------------------------
1242 -- Set_SCO_Pragma_Enabled --
1243 ----------------------------
1245 procedure Set_SCO_Pragma_Enabled (Loc : Source_Ptr) is
1247 -- SCO annotations are not processed after the filtering pass
1249 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1251 Index : Nat;
1253 begin
1254 -- Nothing to do if not generating SCO, or if we're not processing the
1255 -- original source occurrence of the pragma.
1257 if not (Generate_SCO
1258 and then In_Extended_Main_Source_Unit (Loc)
1259 and then not (In_Instance or In_Inlined_Body))
1260 then
1261 return;
1262 end if;
1264 -- Note: the reason we use the Sloc value as the key is that in the
1265 -- generic case, the call to this procedure is made on a copy of the
1266 -- original node, so we can't use the Node_Id value.
1268 Index := SCO_Raw_Hash_Table.Get (Loc);
1270 -- A zero index here indicates that semantic analysis found an
1271 -- activated pragma at Loc which does not have a corresponding pragma
1272 -- or aspect at the syntax level. This may occur in legitimate cases
1273 -- because of expanded code (such are Pre/Post conditions generated for
1274 -- formal parameter validity checks), or as a consequence of a previous
1275 -- error.
1277 if Index = 0 then
1278 return;
1280 else
1281 declare
1282 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1284 begin
1285 -- Note: may be called multiple times for the same sloc, so
1286 -- account for the fact that the entry may already have been
1287 -- marked enabled.
1289 case T.C1 is
1290 -- Aspect (decision SCO)
1292 when 'a' =>
1293 T.C1 := 'A';
1295 when 'A' =>
1296 null;
1298 -- Pragma (statement SCO)
1300 when 'S' =>
1301 pragma Assert (T.C2 = 'p' or else T.C2 = 'P');
1302 T.C2 := 'P';
1304 when others =>
1305 raise Program_Error;
1306 end case;
1307 end;
1308 end if;
1309 end Set_SCO_Pragma_Enabled;
1311 -------------------------
1312 -- Set_Raw_Table_Entry --
1313 -------------------------
1315 procedure Set_Raw_Table_Entry
1316 (C1 : Character;
1317 C2 : Character;
1318 From : Source_Ptr;
1319 To : Source_Ptr;
1320 Last : Boolean;
1321 Pragma_Sloc : Source_Ptr := No_Location;
1322 Pragma_Aspect_Name : Name_Id := No_Name)
1324 pragma Assert (SCO_Generation_State = Raw);
1325 begin
1326 SCO_Raw_Table.Append
1327 ((C1 => C1,
1328 C2 => C2,
1329 From => To_Source_Location (From),
1330 To => To_Source_Location (To),
1331 Last => Last,
1332 Pragma_Sloc => Pragma_Sloc,
1333 Pragma_Aspect_Name => Pragma_Aspect_Name));
1334 end Set_Raw_Table_Entry;
1336 ------------------------
1337 -- To_Source_Location --
1338 ------------------------
1340 function To_Source_Location (S : Source_Ptr) return Source_Location is
1341 begin
1342 if S = No_Location then
1343 return No_Source_Location;
1344 else
1345 return
1346 (Line => Get_Logical_Line_Number (S),
1347 Col => Get_Column_Number (S));
1348 end if;
1349 end To_Source_Location;
1351 -----------------------------------------
1352 -- Traverse_Declarations_Or_Statements --
1353 -----------------------------------------
1355 -- Tables used by Traverse_Declarations_Or_Statements for temporarily
1356 -- holding statement and decision entries. These are declared globally
1357 -- since they are shared by recursive calls to this procedure.
1359 type SC_Entry is record
1360 N : Node_Id;
1361 From : Source_Ptr;
1362 To : Source_Ptr;
1363 Typ : Character;
1364 end record;
1365 -- Used to store a single entry in the following table, From:To represents
1366 -- the range of entries in the CS line entry, and typ is the type, with
1367 -- space meaning that no type letter will accompany the entry.
1369 package SC is new Table.Table
1370 (Table_Component_Type => SC_Entry,
1371 Table_Index_Type => Nat,
1372 Table_Low_Bound => 1,
1373 Table_Initial => 1000,
1374 Table_Increment => 200,
1375 Table_Name => "SCO_SC");
1376 -- Used to store statement components for a CS entry to be output as a
1377 -- result of the call to this procedure. SC.Last is the last entry stored,
1378 -- so the current statement sequence is represented by SC_Array (SC_First
1379 -- .. SC.Last), where SC_First is saved on entry to each recursive call to
1380 -- the routine.
1382 -- Extend_Statement_Sequence adds an entry to this array, and then
1383 -- Set_Statement_Entry clears the entries starting with SC_First, copying
1384 -- these entries to the main SCO output table. The reason that we do the
1385 -- temporary caching of results in this array is that we want the SCO table
1386 -- entries for a given CS line to be contiguous, and the processing may
1387 -- output intermediate entries such as decision entries.
1389 type SD_Entry is record
1390 Nod : Node_Id;
1391 Lst : List_Id;
1392 Typ : Character;
1393 Plo : Source_Ptr;
1394 end record;
1395 -- Used to store a single entry in the following table. Nod is the node to
1396 -- be searched for decisions for the case of Process_Decisions_Defer with a
1397 -- node argument (with Lst set to No_List. Lst is the list to be searched
1398 -- for decisions for the case of Process_Decisions_Defer with a List
1399 -- argument (in which case Nod is set to Empty). Plo is the sloc of the
1400 -- enclosing pragma, if any.
1402 package SD is new Table.Table
1403 (Table_Component_Type => SD_Entry,
1404 Table_Index_Type => Nat,
1405 Table_Low_Bound => 1,
1406 Table_Initial => 1000,
1407 Table_Increment => 200,
1408 Table_Name => "SCO_SD");
1409 -- Used to store possible decision information. Instead of calling the
1410 -- Process_Decisions procedures directly, we call Process_Decisions_Defer,
1411 -- which simply stores the arguments in this table. Then when we clear
1412 -- out a statement sequence using Set_Statement_Entry, after generating
1413 -- the CS lines for the statements, the entries in this table result in
1414 -- calls to Process_Decision. The reason for doing things this way is to
1415 -- ensure that decisions are output after the CS line for the statements
1416 -- in which the decisions occur.
1418 procedure Traverse_Declarations_Or_Statements
1419 (L : List_Id;
1420 D : Dominant_Info := No_Dominant;
1421 P : Node_Id := Empty)
1423 Discard_Dom : Dominant_Info;
1424 pragma Warnings (Off, Discard_Dom);
1425 begin
1426 Discard_Dom := Traverse_Declarations_Or_Statements (L, D, P);
1427 end Traverse_Declarations_Or_Statements;
1429 function Traverse_Declarations_Or_Statements
1430 (L : List_Id;
1431 D : Dominant_Info := No_Dominant;
1432 P : Node_Id := Empty) return Dominant_Info
1434 Current_Dominant : Dominant_Info := D;
1435 -- Dominance information for the current basic block
1437 Current_Test : Node_Id;
1438 -- Conditional node (N_If_Statement or N_Elsif being processed)
1440 N : Node_Id;
1442 SC_First : constant Nat := SC.Last + 1;
1443 SD_First : constant Nat := SD.Last + 1;
1444 -- Record first entries used in SC/SD at this recursive level
1446 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character);
1447 -- Extend the current statement sequence to encompass the node N. Typ is
1448 -- the letter that identifies the type of statement/declaration that is
1449 -- being added to the sequence.
1451 procedure Process_Decisions_Defer (N : Node_Id; T : Character);
1452 pragma Inline (Process_Decisions_Defer);
1453 -- This routine is logically the same as Process_Decisions, except that
1454 -- the arguments are saved in the SD table for later processing when
1455 -- Set_Statement_Entry is called, which goes through the saved entries
1456 -- making the corresponding calls to Process_Decision. Note: the
1457 -- enclosing statement must have already been added to the current
1458 -- statement sequence, so that nested decisions are properly
1459 -- identified as such.
1461 procedure Process_Decisions_Defer (L : List_Id; T : Character);
1462 pragma Inline (Process_Decisions_Defer);
1463 -- Same case for list arguments, deferred call to Process_Decisions
1465 procedure Set_Statement_Entry;
1466 -- Output CS entries for all statements saved in table SC, and end the
1467 -- current CS sequence. Then output entries for all decisions nested in
1468 -- these statements, which have been deferred so far.
1470 procedure Traverse_One (N : Node_Id);
1471 -- Traverse one declaration or statement
1473 procedure Traverse_Aspects (N : Node_Id);
1474 -- Helper for Traverse_One: traverse N's aspect specifications
1476 procedure Traverse_Degenerate_Subprogram (N : Node_Id);
1477 -- Common code to handle null procedures and expression functions. Emit
1478 -- a SCO of the given Kind and N outside of the dominance flow.
1480 -------------------------------
1481 -- Extend_Statement_Sequence --
1482 -------------------------------
1484 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character) is
1485 Dummy : Source_Ptr;
1486 F : Source_Ptr;
1487 T : Source_Ptr;
1488 To_Node : Node_Id := Empty;
1490 begin
1491 Sloc_Range (N, F, T);
1493 case Nkind (N) is
1494 when N_Accept_Statement =>
1495 if Present (Parameter_Specifications (N)) then
1496 To_Node := Last (Parameter_Specifications (N));
1497 elsif Present (Entry_Index (N)) then
1498 To_Node := Entry_Index (N);
1499 else
1500 To_Node := Entry_Direct_Name (N);
1501 end if;
1503 when N_Case_Statement =>
1504 To_Node := Expression (N);
1506 when N_Elsif_Part
1507 | N_If_Statement
1509 To_Node := Condition (N);
1511 when N_Extended_Return_Statement =>
1512 To_Node := Last (Return_Object_Declarations (N));
1514 when N_Loop_Statement =>
1515 To_Node := Iteration_Scheme (N);
1517 when N_Asynchronous_Select
1518 | N_Conditional_Entry_Call
1519 | N_Selective_Accept
1520 | N_Single_Protected_Declaration
1521 | N_Single_Task_Declaration
1522 | N_Timed_Entry_Call
1524 T := F;
1526 when N_Protected_Type_Declaration
1527 | N_Task_Type_Declaration
1529 if Has_Aspects (N) then
1530 To_Node := Last (Aspect_Specifications (N));
1532 elsif Present (Discriminant_Specifications (N)) then
1533 To_Node := Last (Discriminant_Specifications (N));
1535 else
1536 To_Node := Defining_Identifier (N);
1537 end if;
1539 when N_Subexpr =>
1540 To_Node := N;
1542 when others =>
1543 null;
1544 end case;
1546 if Present (To_Node) then
1547 Sloc_Range (To_Node, Dummy, T);
1548 end if;
1550 SC.Append ((N, F, T, Typ));
1551 end Extend_Statement_Sequence;
1553 -----------------------------
1554 -- Process_Decisions_Defer --
1555 -----------------------------
1557 procedure Process_Decisions_Defer (N : Node_Id; T : Character) is
1558 begin
1559 SD.Append ((N, No_List, T, Current_Pragma_Sloc));
1560 end Process_Decisions_Defer;
1562 procedure Process_Decisions_Defer (L : List_Id; T : Character) is
1563 begin
1564 SD.Append ((Empty, L, T, Current_Pragma_Sloc));
1565 end Process_Decisions_Defer;
1567 -------------------------
1568 -- Set_Statement_Entry --
1569 -------------------------
1571 procedure Set_Statement_Entry is
1572 SC_Last : constant Int := SC.Last;
1573 SD_Last : constant Int := SD.Last;
1575 begin
1576 -- Output statement entries from saved entries in SC table
1578 for J in SC_First .. SC_Last loop
1579 if J = SC_First then
1581 if Current_Dominant /= No_Dominant then
1582 declare
1583 From : Source_Ptr;
1584 To : Source_Ptr;
1586 begin
1587 Sloc_Range (Current_Dominant.N, From, To);
1589 if Current_Dominant.K /= 'E' then
1590 To := No_Location;
1591 end if;
1593 -- Be consistent with the location determined in
1594 -- Output_Header.
1596 if Current_Dominant.K = 'T'
1597 and then Nkind (Parent (Current_Dominant.N))
1598 in N_Accept_Alternative
1599 | N_Delay_Alternative
1600 | N_Terminate_Alternative
1601 then
1602 From := First_Sloc (Current_Dominant.N);
1603 end if;
1605 Set_Raw_Table_Entry
1606 (C1 => '>',
1607 C2 => Current_Dominant.K,
1608 From => From,
1609 To => To,
1610 Last => False,
1611 Pragma_Sloc => No_Location,
1612 Pragma_Aspect_Name => No_Name);
1613 end;
1614 end if;
1615 end if;
1617 declare
1618 SCE : SC_Entry renames SC.Table (J);
1619 Pragma_Sloc : Source_Ptr := No_Location;
1620 Pragma_Aspect_Name : Name_Id := No_Name;
1622 begin
1623 -- For the case of a statement SCO for a pragma controlled by
1624 -- Set_SCO_Pragma_Enabled, set Pragma_Sloc so that the SCO (and
1625 -- those of any nested decision) is emitted only if the pragma
1626 -- is enabled.
1628 if SCE.Typ = 'p' then
1629 Pragma_Sloc := SCE.From;
1630 SCO_Raw_Hash_Table.Set
1631 (Pragma_Sloc, SCO_Raw_Table.Last + 1);
1632 Pragma_Aspect_Name := Pragma_Name_Unmapped (SCE.N);
1633 pragma Assert (Pragma_Aspect_Name /= No_Name);
1635 elsif SCE.Typ = 'P' then
1636 Pragma_Aspect_Name := Pragma_Name_Unmapped (SCE.N);
1637 pragma Assert (Pragma_Aspect_Name /= No_Name);
1638 end if;
1640 Set_Raw_Table_Entry
1641 (C1 => 'S',
1642 C2 => SCE.Typ,
1643 From => SCE.From,
1644 To => SCE.To,
1645 Last => (J = SC_Last),
1646 Pragma_Sloc => Pragma_Sloc,
1647 Pragma_Aspect_Name => Pragma_Aspect_Name);
1648 end;
1649 end loop;
1651 -- Last statement of basic block, if present, becomes new current
1652 -- dominant.
1654 if SC_Last >= SC_First then
1655 Current_Dominant := ('S', SC.Table (SC_Last).N);
1656 end if;
1658 -- Clear out used section of SC table
1660 SC.Set_Last (SC_First - 1);
1662 -- Output any embedded decisions
1664 for J in SD_First .. SD_Last loop
1665 declare
1666 SDE : SD_Entry renames SD.Table (J);
1668 begin
1669 if Present (SDE.Nod) then
1670 Process_Decisions (SDE.Nod, SDE.Typ, SDE.Plo);
1671 else
1672 Process_Decisions (SDE.Lst, SDE.Typ, SDE.Plo);
1673 end if;
1674 end;
1675 end loop;
1677 -- Clear out used section of SD table
1679 SD.Set_Last (SD_First - 1);
1680 end Set_Statement_Entry;
1682 ----------------------
1683 -- Traverse_Aspects --
1684 ----------------------
1686 procedure Traverse_Aspects (N : Node_Id) is
1687 AE : Node_Id;
1688 AN : Node_Id;
1689 C1 : Character;
1691 begin
1692 AN := First (Aspect_Specifications (N));
1693 while Present (AN) loop
1694 AE := Expression (AN);
1696 -- SCOs are generated before semantic analysis/expansion:
1697 -- PPCs are not split yet.
1699 pragma Assert (not Split_PPC (AN));
1701 C1 := ASCII.NUL;
1703 case Get_Aspect_Id (AN) is
1705 -- Aspects rewritten into pragmas controlled by a Check_Policy:
1706 -- Current_Pragma_Sloc must be set to the sloc of the aspect
1707 -- specification. The corresponding pragma will have the same
1708 -- sloc. Note that Invariant, Pre, and Post will be enabled if
1709 -- the policy is Check; on the other hand, predicate aspects
1710 -- will be enabled for Check and Ignore (when Add_Predicate
1711 -- is called) because the actual checks occur in client units.
1712 -- When the assertion policy for Predicate is Disable, the
1713 -- SCO remains disabled, because Add_Predicate is never called.
1715 -- Pre/post can have checks in client units too because of
1716 -- inheritance, so should they receive the same treatment???
1718 when Aspect_Dynamic_Predicate
1719 | Aspect_Invariant
1720 | Aspect_Post
1721 | Aspect_Postcondition
1722 | Aspect_Pre
1723 | Aspect_Precondition
1724 | Aspect_Predicate
1725 | Aspect_Static_Predicate
1726 | Aspect_Type_Invariant
1728 C1 := 'a';
1730 -- Other aspects: just process any decision nested in the
1731 -- aspect expression.
1733 when others =>
1734 if Has_Decision (AE) then
1735 C1 := 'X';
1736 end if;
1737 end case;
1739 if C1 /= ASCII.NUL then
1740 pragma Assert (Current_Pragma_Sloc = No_Location);
1742 if C1 = 'a' or else C1 = 'A' then
1743 Current_Pragma_Sloc := Sloc (AN);
1744 end if;
1746 Process_Decisions_Defer (AE, C1);
1748 Current_Pragma_Sloc := No_Location;
1749 end if;
1751 Next (AN);
1752 end loop;
1753 end Traverse_Aspects;
1755 ------------------------------------
1756 -- Traverse_Degenerate_Subprogram --
1757 ------------------------------------
1759 procedure Traverse_Degenerate_Subprogram (N : Node_Id) is
1760 begin
1761 -- Complete current sequence of statements
1763 Set_Statement_Entry;
1765 declare
1766 Saved_Dominant : constant Dominant_Info := Current_Dominant;
1767 -- Save last statement in current sequence as dominant
1769 begin
1770 -- Output statement SCO for degenerate subprogram body (null
1771 -- statement or freestanding expression) outside of the dominance
1772 -- chain.
1774 Current_Dominant := No_Dominant;
1775 Extend_Statement_Sequence (N, Typ => 'X');
1777 -- For the case of an expression-function, collect decisions
1778 -- embedded in the expression now.
1780 if Nkind (N) in N_Subexpr then
1781 Process_Decisions_Defer (N, 'X');
1782 end if;
1784 Set_Statement_Entry;
1786 -- Restore current dominant information designating last statement
1787 -- in previous sequence (i.e. make the dominance chain skip over
1788 -- the degenerate body).
1790 Current_Dominant := Saved_Dominant;
1791 end;
1792 end Traverse_Degenerate_Subprogram;
1794 ------------------
1795 -- Traverse_One --
1796 ------------------
1798 procedure Traverse_One (N : Node_Id) is
1799 begin
1800 -- Initialize or extend current statement sequence. Note that for
1801 -- special cases such as IF and Case statements we will modify
1802 -- the range to exclude internal statements that should not be
1803 -- counted as part of the current statement sequence.
1805 case Nkind (N) is
1807 -- Package declaration
1809 when N_Package_Declaration =>
1810 Set_Statement_Entry;
1811 Traverse_Package_Declaration (N, Current_Dominant);
1813 -- Generic package declaration
1815 when N_Generic_Package_Declaration =>
1816 Set_Statement_Entry;
1817 Traverse_Generic_Package_Declaration (N);
1819 -- Package body
1821 when N_Package_Body =>
1822 Set_Statement_Entry;
1823 Traverse_Package_Body (N);
1825 -- Subprogram declaration or subprogram body stub
1827 when N_Expression_Function
1828 | N_Subprogram_Body_Stub
1829 | N_Subprogram_Declaration
1831 declare
1832 Spec : constant Node_Id := Specification (N);
1833 begin
1834 Process_Decisions_Defer
1835 (Parameter_Specifications (Spec), 'X');
1837 -- Case of a null procedure: generate SCO for fictitious
1838 -- NULL statement located at the NULL keyword in the
1839 -- procedure specification.
1841 if Nkind (N) = N_Subprogram_Declaration
1842 and then Nkind (Spec) = N_Procedure_Specification
1843 and then Null_Present (Spec)
1844 then
1845 Traverse_Degenerate_Subprogram (Null_Statement (Spec));
1847 -- Case of an expression function: generate a statement SCO
1848 -- for the expression (and then decision SCOs for any nested
1849 -- decisions).
1851 elsif Nkind (N) = N_Expression_Function then
1852 Traverse_Degenerate_Subprogram (Expression (N));
1853 end if;
1854 end;
1856 -- Entry declaration
1858 when N_Entry_Declaration =>
1859 Process_Decisions_Defer (Parameter_Specifications (N), 'X');
1861 -- Generic subprogram declaration
1863 when N_Generic_Subprogram_Declaration =>
1864 Process_Decisions_Defer
1865 (Generic_Formal_Declarations (N), 'X');
1866 Process_Decisions_Defer
1867 (Parameter_Specifications (Specification (N)), 'X');
1869 -- Task or subprogram body
1871 when N_Subprogram_Body
1872 | N_Task_Body
1874 Set_Statement_Entry;
1875 Traverse_Subprogram_Or_Task_Body (N);
1877 -- Entry body
1879 when N_Entry_Body =>
1880 declare
1881 Cond : constant Node_Id :=
1882 Condition (Entry_Body_Formal_Part (N));
1884 Inner_Dominant : Dominant_Info := No_Dominant;
1886 begin
1887 Set_Statement_Entry;
1889 if Present (Cond) then
1890 Process_Decisions_Defer (Cond, 'G');
1892 -- For an entry body with a barrier, the entry body
1893 -- is dominated by a True evaluation of the barrier.
1895 Inner_Dominant := ('T', N);
1896 end if;
1898 Traverse_Subprogram_Or_Task_Body (N, Inner_Dominant);
1899 end;
1901 -- Protected body
1903 when N_Protected_Body =>
1904 Set_Statement_Entry;
1905 Traverse_Declarations_Or_Statements (Declarations (N));
1907 -- Exit statement, which is an exit statement in the SCO sense,
1908 -- so it is included in the current statement sequence, but
1909 -- then it terminates this sequence. We also have to process
1910 -- any decisions in the exit statement expression.
1912 when N_Exit_Statement =>
1913 Extend_Statement_Sequence (N, 'E');
1914 Process_Decisions_Defer (Condition (N), 'E');
1915 Set_Statement_Entry;
1917 -- If condition is present, then following statement is
1918 -- only executed if the condition evaluates to False.
1920 if Present (Condition (N)) then
1921 Current_Dominant := ('F', N);
1922 else
1923 Current_Dominant := No_Dominant;
1924 end if;
1926 -- Label, which breaks the current statement sequence, but the
1927 -- label itself is not included in the next statement sequence,
1928 -- since it generates no code.
1930 when N_Label =>
1931 Set_Statement_Entry;
1932 Current_Dominant := No_Dominant;
1934 -- Block statement, which breaks the current statement sequence
1936 when N_Block_Statement =>
1937 Set_Statement_Entry;
1939 -- The first statement in the handled sequence of statements
1940 -- is dominated by the elaboration of the last declaration.
1942 Current_Dominant := Traverse_Declarations_Or_Statements
1943 (L => Declarations (N),
1944 D => Current_Dominant);
1946 Traverse_Handled_Statement_Sequence
1947 (N => Handled_Statement_Sequence (N),
1948 D => Current_Dominant);
1950 -- If statement, which breaks the current statement sequence,
1951 -- but we include the condition in the current sequence.
1953 when N_If_Statement =>
1954 Current_Test := N;
1955 Extend_Statement_Sequence (N, 'I');
1956 Process_Decisions_Defer (Condition (N), 'I');
1957 Set_Statement_Entry;
1959 -- Now we traverse the statements in the THEN part
1961 Traverse_Declarations_Or_Statements
1962 (L => Then_Statements (N),
1963 D => ('T', N));
1965 -- Loop through ELSIF parts if present
1967 if Present (Elsif_Parts (N)) then
1968 declare
1969 Saved_Dominant : constant Dominant_Info :=
1970 Current_Dominant;
1972 Elif : Node_Id := First (Elsif_Parts (N));
1974 begin
1975 while Present (Elif) loop
1977 -- An Elsif is executed only if the previous test
1978 -- got a FALSE outcome.
1980 Current_Dominant := ('F', Current_Test);
1982 -- Now update current test information
1984 Current_Test := Elif;
1986 -- We generate a statement sequence for the
1987 -- construct "ELSIF condition", so that we have
1988 -- a statement for the resulting decisions.
1990 Extend_Statement_Sequence (Elif, 'I');
1991 Process_Decisions_Defer (Condition (Elif), 'I');
1992 Set_Statement_Entry;
1994 -- An ELSIF part is never guaranteed to have
1995 -- been executed, following statements are only
1996 -- dominated by the initial IF statement.
1998 Current_Dominant := Saved_Dominant;
2000 -- Traverse the statements in the ELSIF
2002 Traverse_Declarations_Or_Statements
2003 (L => Then_Statements (Elif),
2004 D => ('T', Elif));
2005 Next (Elif);
2006 end loop;
2007 end;
2008 end if;
2010 -- Finally traverse the ELSE statements if present
2012 Traverse_Declarations_Or_Statements
2013 (L => Else_Statements (N),
2014 D => ('F', Current_Test));
2016 -- CASE statement, which breaks the current statement sequence,
2017 -- but we include the expression in the current sequence.
2019 when N_Case_Statement =>
2020 Extend_Statement_Sequence (N, 'C');
2021 Process_Decisions_Defer (Expression (N), 'X');
2022 Set_Statement_Entry;
2024 -- Process case branches, all of which are dominated by the
2025 -- CASE statement.
2027 declare
2028 Alt : Node_Id;
2029 begin
2030 Alt := First_Non_Pragma (Alternatives (N));
2031 while Present (Alt) loop
2032 Traverse_Declarations_Or_Statements
2033 (L => Statements (Alt),
2034 D => Current_Dominant);
2035 Next (Alt);
2036 end loop;
2037 end;
2039 -- ACCEPT statement
2041 when N_Accept_Statement =>
2042 Extend_Statement_Sequence (N, 'A');
2043 Set_Statement_Entry;
2045 -- Process sequence of statements, dominant is the ACCEPT
2046 -- statement.
2048 Traverse_Handled_Statement_Sequence
2049 (N => Handled_Statement_Sequence (N),
2050 D => Current_Dominant);
2052 -- SELECT
2054 when N_Selective_Accept =>
2055 Extend_Statement_Sequence (N, 'S');
2056 Set_Statement_Entry;
2058 -- Process alternatives
2060 declare
2061 Alt : Node_Id;
2062 Guard : Node_Id;
2063 S_Dom : Dominant_Info;
2065 begin
2066 Alt := First (Select_Alternatives (N));
2067 while Present (Alt) loop
2068 S_Dom := Current_Dominant;
2069 Guard := Condition (Alt);
2071 if Present (Guard) then
2072 Process_Decisions
2073 (Guard,
2074 'G',
2075 Pragma_Sloc => No_Location);
2076 Current_Dominant := ('T', Guard);
2077 end if;
2079 Traverse_One (Alt);
2081 Current_Dominant := S_Dom;
2082 Next (Alt);
2083 end loop;
2084 end;
2086 Traverse_Declarations_Or_Statements
2087 (L => Else_Statements (N),
2088 D => Current_Dominant);
2090 when N_Conditional_Entry_Call
2091 | N_Timed_Entry_Call
2093 Extend_Statement_Sequence (N, 'S');
2094 Set_Statement_Entry;
2096 -- Process alternatives
2098 Traverse_One (Entry_Call_Alternative (N));
2100 if Nkind (N) = N_Timed_Entry_Call then
2101 Traverse_One (Delay_Alternative (N));
2102 else
2103 Traverse_Declarations_Or_Statements
2104 (L => Else_Statements (N),
2105 D => Current_Dominant);
2106 end if;
2108 when N_Asynchronous_Select =>
2109 Extend_Statement_Sequence (N, 'S');
2110 Set_Statement_Entry;
2112 Traverse_One (Triggering_Alternative (N));
2113 Traverse_Declarations_Or_Statements
2114 (L => Statements (Abortable_Part (N)),
2115 D => Current_Dominant);
2117 when N_Accept_Alternative =>
2118 Traverse_Declarations_Or_Statements
2119 (L => Statements (N),
2120 D => Current_Dominant,
2121 P => Accept_Statement (N));
2123 when N_Entry_Call_Alternative =>
2124 Traverse_Declarations_Or_Statements
2125 (L => Statements (N),
2126 D => Current_Dominant,
2127 P => Entry_Call_Statement (N));
2129 when N_Delay_Alternative =>
2130 Traverse_Declarations_Or_Statements
2131 (L => Statements (N),
2132 D => Current_Dominant,
2133 P => Delay_Statement (N));
2135 when N_Triggering_Alternative =>
2136 Traverse_Declarations_Or_Statements
2137 (L => Statements (N),
2138 D => Current_Dominant,
2139 P => Triggering_Statement (N));
2141 when N_Terminate_Alternative =>
2143 -- It is dubious to emit a statement SCO for a TERMINATE
2144 -- alternative, since no code is actually executed if the
2145 -- alternative is selected -- the tasking runtime call just
2146 -- never returns???
2148 Extend_Statement_Sequence (N, ' ');
2149 Set_Statement_Entry;
2151 -- Unconditional exit points, which are included in the current
2152 -- statement sequence, but then terminate it
2154 when N_Goto_Statement
2155 | N_Raise_Statement
2156 | N_Requeue_Statement
2158 Extend_Statement_Sequence (N, ' ');
2159 Set_Statement_Entry;
2160 Current_Dominant := No_Dominant;
2162 -- Simple return statement. which is an exit point, but we
2163 -- have to process the return expression for decisions.
2165 when N_Simple_Return_Statement =>
2166 Extend_Statement_Sequence (N, ' ');
2167 Process_Decisions_Defer (Expression (N), 'X');
2168 Set_Statement_Entry;
2169 Current_Dominant := No_Dominant;
2171 -- Extended return statement
2173 when N_Extended_Return_Statement =>
2174 Extend_Statement_Sequence (N, 'R');
2175 Process_Decisions_Defer (Return_Object_Declarations (N), 'X');
2176 Set_Statement_Entry;
2178 Traverse_Handled_Statement_Sequence
2179 (N => Handled_Statement_Sequence (N),
2180 D => Current_Dominant);
2182 Current_Dominant := No_Dominant;
2184 -- Loop ends the current statement sequence, but we include
2185 -- the iteration scheme if present in the current sequence.
2186 -- But the body of the loop starts a new sequence, since it
2187 -- may not be executed as part of the current sequence.
2189 when N_Loop_Statement =>
2190 declare
2191 ISC : constant Node_Id := Iteration_Scheme (N);
2192 Inner_Dominant : Dominant_Info := No_Dominant;
2194 begin
2195 if Present (ISC) then
2197 -- If iteration scheme present, extend the current
2198 -- statement sequence to include the iteration scheme
2199 -- and process any decisions it contains.
2201 -- While loop
2203 if Present (Condition (ISC)) then
2204 Extend_Statement_Sequence (N, 'W');
2205 Process_Decisions_Defer (Condition (ISC), 'W');
2207 -- Set more specific dominant for inner statements
2208 -- (the control sloc for the decision is that of
2209 -- the WHILE token).
2211 Inner_Dominant := ('T', ISC);
2213 -- For loop
2215 else
2216 Extend_Statement_Sequence (N, 'F');
2217 Process_Decisions_Defer
2218 (Loop_Parameter_Specification (ISC), 'X');
2219 end if;
2220 end if;
2222 Set_Statement_Entry;
2224 if Inner_Dominant = No_Dominant then
2225 Inner_Dominant := Current_Dominant;
2226 end if;
2228 Traverse_Declarations_Or_Statements
2229 (L => Statements (N),
2230 D => Inner_Dominant);
2231 end;
2233 -- Pragma
2235 when N_Pragma =>
2237 -- Record sloc of pragma (pragmas don't nest)
2239 pragma Assert (Current_Pragma_Sloc = No_Location);
2240 Current_Pragma_Sloc := Sloc (N);
2242 -- Processing depends on the kind of pragma
2244 declare
2245 Nam : constant Name_Id := Pragma_Name_Unmapped (N);
2246 Arg : Node_Id :=
2247 First (Pragma_Argument_Associations (N));
2248 Typ : Character;
2250 begin
2251 case Nam is
2252 when Name_Assert
2253 | Name_Assert_And_Cut
2254 | Name_Assume
2255 | Name_Check
2256 | Name_Loop_Invariant
2257 | Name_Postcondition
2258 | Name_Precondition
2259 | Name_Type_Invariant
2260 | Name_Invariant
2262 -- For Assert/Check/Precondition/Postcondition, we
2263 -- must generate a P entry for the decision. Note
2264 -- that this is done unconditionally at this stage.
2265 -- Output for disabled pragmas is suppressed later
2266 -- on when we output the decision line in Put_SCOs,
2267 -- depending on setting by Set_SCO_Pragma_Enabled.
2269 if Nam = Name_Check
2270 or else Nam = Name_Type_Invariant
2271 or else Nam = Name_Invariant
2272 then
2273 Next (Arg);
2274 end if;
2276 Process_Decisions_Defer (Expression (Arg), 'P');
2277 Typ := 'p';
2279 -- Pre/postconditions can be inherited so SCO should
2280 -- never be deactivated???
2282 when Name_Debug =>
2283 if Present (Arg) and then Present (Next (Arg)) then
2285 -- Case of a dyadic pragma Debug: first argument
2286 -- is a P decision, any nested decision in the
2287 -- second argument is an X decision.
2289 Process_Decisions_Defer (Expression (Arg), 'P');
2290 Next (Arg);
2291 end if;
2293 Process_Decisions_Defer (Expression (Arg), 'X');
2294 Typ := 'p';
2296 -- For all other pragmas, we generate decision entries
2297 -- for any embedded expressions, and the pragma is
2298 -- never disabled.
2300 -- Should generate P decisions (not X) for assertion
2301 -- related pragmas: [{Static,Dynamic}_]Predicate???
2303 when others =>
2304 Process_Decisions_Defer (N, 'X');
2305 Typ := 'P';
2306 end case;
2308 -- Add statement SCO
2310 Extend_Statement_Sequence (N, Typ);
2312 Current_Pragma_Sloc := No_Location;
2313 end;
2315 -- Object declaration. Ignored if Prev_Ids is set, since the
2316 -- parser generates multiple instances of the whole declaration
2317 -- if there is more than one identifier declared, and we only
2318 -- want one entry in the SCOs, so we take the first, for which
2319 -- Prev_Ids is False.
2321 when N_Number_Declaration
2322 | N_Object_Declaration
2324 if not Prev_Ids (N) then
2325 Extend_Statement_Sequence (N, 'o');
2327 if Has_Decision (N) then
2328 Process_Decisions_Defer (N, 'X');
2329 end if;
2330 end if;
2332 -- All other cases, which extend the current statement sequence
2333 -- but do not terminate it, even if they have nested decisions.
2335 when N_Protected_Type_Declaration
2336 | N_Task_Type_Declaration
2338 Extend_Statement_Sequence (N, 't');
2339 Process_Decisions_Defer (Discriminant_Specifications (N), 'X');
2340 Set_Statement_Entry;
2342 Traverse_Protected_Or_Task_Definition (N);
2344 when N_Single_Protected_Declaration
2345 | N_Single_Task_Declaration
2347 Extend_Statement_Sequence (N, 'o');
2348 Set_Statement_Entry;
2350 Traverse_Protected_Or_Task_Definition (N);
2352 when others =>
2354 -- Determine required type character code, or ASCII.NUL if
2355 -- no SCO should be generated for this node.
2357 declare
2358 NK : constant Node_Kind := Nkind (N);
2359 Typ : Character;
2361 begin
2362 case NK is
2363 when N_Full_Type_Declaration
2364 | N_Incomplete_Type_Declaration
2365 | N_Private_Extension_Declaration
2366 | N_Private_Type_Declaration
2368 Typ := 't';
2370 when N_Subtype_Declaration =>
2371 Typ := 's';
2373 when N_Renaming_Declaration =>
2374 Typ := 'r';
2376 when N_Generic_Instantiation =>
2377 Typ := 'i';
2379 when N_Package_Body_Stub
2380 | N_Protected_Body_Stub
2381 | N_Representation_Clause
2382 | N_Task_Body_Stub
2383 | N_Use_Package_Clause
2384 | N_Use_Type_Clause
2386 Typ := ASCII.NUL;
2388 when N_Procedure_Call_Statement =>
2389 Typ := ' ';
2391 when others =>
2392 if NK in N_Statement_Other_Than_Procedure_Call then
2393 Typ := ' ';
2394 else
2395 Typ := 'd';
2396 end if;
2397 end case;
2399 if Typ /= ASCII.NUL then
2400 Extend_Statement_Sequence (N, Typ);
2401 end if;
2402 end;
2404 -- Process any embedded decisions
2406 if Has_Decision (N) then
2407 Process_Decisions_Defer (N, 'X');
2408 end if;
2409 end case;
2411 -- Process aspects if present
2413 Traverse_Aspects (N);
2414 end Traverse_One;
2416 -- Start of processing for Traverse_Declarations_Or_Statements
2418 begin
2419 -- Process single prefixed node
2421 if Present (P) then
2422 Traverse_One (P);
2423 end if;
2425 -- Loop through statements or declarations
2427 N := First (L);
2428 while Present (N) loop
2430 -- Note: For separate bodies, we see the tree after Par.Labl has
2431 -- introduced implicit labels, so we need to ignore those nodes.
2433 if Nkind (N) /= N_Implicit_Label_Declaration then
2434 Traverse_One (N);
2435 end if;
2437 Next (N);
2438 end loop;
2440 -- End sequence of statements and flush deferred decisions
2442 if Present (P) or else Is_Non_Empty_List (L) then
2443 Set_Statement_Entry;
2444 end if;
2446 return Current_Dominant;
2447 end Traverse_Declarations_Or_Statements;
2449 ------------------------------------------
2450 -- Traverse_Generic_Package_Declaration --
2451 ------------------------------------------
2453 procedure Traverse_Generic_Package_Declaration (N : Node_Id) is
2454 begin
2455 Process_Decisions (Generic_Formal_Declarations (N), 'X', No_Location);
2456 Traverse_Package_Declaration (N);
2457 end Traverse_Generic_Package_Declaration;
2459 -----------------------------------------
2460 -- Traverse_Handled_Statement_Sequence --
2461 -----------------------------------------
2463 procedure Traverse_Handled_Statement_Sequence
2464 (N : Node_Id;
2465 D : Dominant_Info := No_Dominant)
2467 Handler : Node_Id;
2469 begin
2470 -- For package bodies without a statement part, the parser adds an empty
2471 -- one, to normalize the representation. The null statement therein,
2472 -- which does not come from source, does not get a SCO.
2474 if Present (N) and then Comes_From_Source (N) then
2475 Traverse_Declarations_Or_Statements (Statements (N), D);
2477 if Present (Exception_Handlers (N)) then
2478 Handler := First_Non_Pragma (Exception_Handlers (N));
2479 while Present (Handler) loop
2480 Traverse_Declarations_Or_Statements
2481 (L => Statements (Handler),
2482 D => ('E', Handler));
2483 Next (Handler);
2484 end loop;
2485 end if;
2486 end if;
2487 end Traverse_Handled_Statement_Sequence;
2489 ---------------------------
2490 -- Traverse_Package_Body --
2491 ---------------------------
2493 procedure Traverse_Package_Body (N : Node_Id) is
2494 Dom : Dominant_Info;
2495 begin
2496 -- The first statement in the handled sequence of statements is
2497 -- dominated by the elaboration of the last declaration.
2499 Dom := Traverse_Declarations_Or_Statements (Declarations (N));
2501 Traverse_Handled_Statement_Sequence
2502 (Handled_Statement_Sequence (N), Dom);
2503 end Traverse_Package_Body;
2505 ----------------------------------
2506 -- Traverse_Package_Declaration --
2507 ----------------------------------
2509 procedure Traverse_Package_Declaration
2510 (N : Node_Id;
2511 D : Dominant_Info := No_Dominant)
2513 Spec : constant Node_Id := Specification (N);
2514 Dom : Dominant_Info;
2516 begin
2517 Dom :=
2518 Traverse_Declarations_Or_Statements (Visible_Declarations (Spec), D);
2520 -- First private declaration is dominated by last visible declaration
2522 Traverse_Declarations_Or_Statements (Private_Declarations (Spec), Dom);
2523 end Traverse_Package_Declaration;
2525 -------------------------------------------
2526 -- Traverse_Protected_Or_Task_Definition --
2527 -------------------------------------------
2529 procedure Traverse_Protected_Or_Task_Definition (N : Node_Id) is
2530 Dom_Info : Dominant_Info := ('S', N);
2531 -- The first declaration is dominated by the protected or task [type]
2532 -- declaration.
2534 Sync_Def : Node_Id;
2535 -- N's protected or task definition
2537 Priv_Decl : List_Id;
2538 Vis_Decl : List_Id;
2539 -- Sync_Def's Visible_Declarations and Private_Declarations
2541 begin
2542 case Nkind (N) is
2543 when N_Protected_Type_Declaration
2544 | N_Single_Protected_Declaration
2546 Sync_Def := Protected_Definition (N);
2548 when N_Single_Task_Declaration
2549 | N_Task_Type_Declaration
2551 Sync_Def := Task_Definition (N);
2553 when others =>
2554 raise Program_Error;
2555 end case;
2557 -- Sync_Def may be Empty at least for empty Task_Type_Declarations.
2558 -- Querying Visible or Private_Declarations is invalid in this case.
2560 if Present (Sync_Def) then
2561 Vis_Decl := Visible_Declarations (Sync_Def);
2562 Priv_Decl := Private_Declarations (Sync_Def);
2563 else
2564 Vis_Decl := No_List;
2565 Priv_Decl := No_List;
2566 end if;
2568 Dom_Info := Traverse_Declarations_Or_Statements
2569 (L => Vis_Decl,
2570 D => Dom_Info);
2572 -- If visible declarations are present, the first private declaration
2573 -- is dominated by the last visible declaration.
2575 Traverse_Declarations_Or_Statements
2576 (L => Priv_Decl,
2577 D => Dom_Info);
2578 end Traverse_Protected_Or_Task_Definition;
2580 --------------------------------------
2581 -- Traverse_Subprogram_Or_Task_Body --
2582 --------------------------------------
2584 procedure Traverse_Subprogram_Or_Task_Body
2585 (N : Node_Id;
2586 D : Dominant_Info := No_Dominant)
2588 Decls : constant List_Id := Declarations (N);
2589 Dom_Info : Dominant_Info := D;
2591 begin
2592 -- If declarations are present, the first statement is dominated by the
2593 -- last declaration.
2595 Dom_Info := Traverse_Declarations_Or_Statements
2596 (L => Decls, D => Dom_Info);
2598 Traverse_Handled_Statement_Sequence
2599 (N => Handled_Statement_Sequence (N),
2600 D => Dom_Info);
2601 end Traverse_Subprogram_Or_Task_Body;
2603 -------------------------
2604 -- SCO_Record_Filtered --
2605 -------------------------
2607 procedure SCO_Record_Filtered is
2608 type Decision is record
2609 Kind : Character;
2610 -- Type of the SCO decision (see comments for SCO_Table_Entry.C1)
2612 Sloc : Source_Location;
2614 Top : Nat;
2615 -- Index in the SCO_Raw_Table for the root operator/condition for the
2616 -- expression that controls the decision.
2617 end record;
2618 -- Decision descriptor: used to gather information about a candidate
2619 -- SCO decision.
2621 package Pending_Decisions is new Table.Table
2622 (Table_Component_Type => Decision,
2623 Table_Index_Type => Nat,
2624 Table_Low_Bound => 1,
2625 Table_Initial => 1000,
2626 Table_Increment => 200,
2627 Table_Name => "Filter_Pending_Decisions");
2628 -- Table used to hold decisions to process during the collection pass
2630 procedure Add_Expression_Tree (Idx : in out Nat);
2631 -- Add SCO raw table entries for the decision controlling expression
2632 -- tree starting at Idx to the filtered SCO table.
2634 procedure Collect_Decisions
2635 (D : Decision;
2636 Next : out Nat);
2637 -- Collect decisions to add to the filtered SCO table starting at the
2638 -- D decision (including it and its nested operators/conditions). Set
2639 -- Next to the first node index passed the whole decision.
2641 procedure Compute_Range
2642 (Idx : in out Nat;
2643 From : out Source_Location;
2644 To : out Source_Location);
2645 -- Compute the source location range for the expression tree starting at
2646 -- Idx in the SCO raw table. Store its bounds in From and To.
2648 function Is_Decision (Idx : Nat) return Boolean;
2649 -- Return if the expression tree starting at Idx has adjacent nested
2650 -- nodes that make a decision.
2652 procedure Process_Pending_Decisions
2653 (Original_Decision : SCO_Table_Entry);
2654 -- Complete the filtered SCO table using collected decisions. Output
2655 -- decisions inherit the pragma information from the original decision.
2657 procedure Search_Nested_Decisions (Idx : in out Nat);
2658 -- Collect decisions to add to the filtered SCO table starting at the
2659 -- node at Idx in the SCO raw table. This node must not be part of an
2660 -- already-processed decision. Set Idx to the first node index passed
2661 -- the whole expression tree.
2663 procedure Skip_Decision
2664 (Idx : in out Nat;
2665 Process_Nested_Decisions : Boolean);
2666 -- Skip all the nodes that belong to the decision starting at Idx. If
2667 -- Process_Nested_Decision, call Search_Nested_Decisions on the first
2668 -- nested nodes that do not belong to the decision. Set Idx to the first
2669 -- node index passed the whole expression tree.
2671 -------------------------
2672 -- Add_Expression_Tree --
2673 -------------------------
2675 procedure Add_Expression_Tree (Idx : in out Nat) is
2676 Node_Idx : constant Nat := Idx;
2677 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Node_Idx);
2678 From : Source_Location;
2679 To : Source_Location;
2681 begin
2682 case T.C1 is
2683 when ' ' =>
2685 -- This is a single condition. Add an entry for it and move on
2687 SCO_Table.Append (T);
2688 Idx := Idx + 1;
2690 when '!' =>
2692 -- This is a NOT operator: add an entry for it and browse its
2693 -- only child.
2695 SCO_Table.Append (T);
2696 Idx := Idx + 1;
2697 Add_Expression_Tree (Idx);
2699 when others =>
2701 -- This must be an AND/OR/AND THEN/OR ELSE operator
2703 if T.C2 = '?' then
2705 -- This is not a short circuit operator: consider this one
2706 -- and all its children as a single condition.
2708 Compute_Range (Idx, From, To);
2709 SCO_Table.Append
2710 ((From => From,
2711 To => To,
2712 C1 => ' ',
2713 C2 => 'c',
2714 Last => False,
2715 Pragma_Sloc => No_Location,
2716 Pragma_Aspect_Name => No_Name));
2718 else
2719 -- This is a real short circuit operator: add an entry for
2720 -- it and browse its children.
2722 SCO_Table.Append (T);
2723 Idx := Idx + 1;
2724 Add_Expression_Tree (Idx);
2725 Add_Expression_Tree (Idx);
2726 end if;
2727 end case;
2728 end Add_Expression_Tree;
2730 -----------------------
2731 -- Collect_Decisions --
2732 -----------------------
2734 procedure Collect_Decisions
2735 (D : Decision;
2736 Next : out Nat)
2738 Idx : Nat := D.Top;
2740 begin
2741 if D.Kind /= 'X' or else Is_Decision (D.Top) then
2742 Pending_Decisions.Append (D);
2743 end if;
2745 Skip_Decision (Idx, True);
2746 Next := Idx;
2747 end Collect_Decisions;
2749 -------------------
2750 -- Compute_Range --
2751 -------------------
2753 procedure Compute_Range
2754 (Idx : in out Nat;
2755 From : out Source_Location;
2756 To : out Source_Location)
2758 Sloc_F : Source_Location := No_Source_Location;
2759 Sloc_T : Source_Location := No_Source_Location;
2761 procedure Process_One;
2762 -- Process one node of the tree, and recurse over children. Update
2763 -- Idx during the traversal.
2765 -----------------
2766 -- Process_One --
2767 -----------------
2769 procedure Process_One is
2770 begin
2771 if Sloc_F = No_Source_Location
2772 or else
2773 SCO_Raw_Table.Table (Idx).From < Sloc_F
2774 then
2775 Sloc_F := SCO_Raw_Table.Table (Idx).From;
2776 end if;
2778 if Sloc_T = No_Source_Location
2779 or else
2780 Sloc_T < SCO_Raw_Table.Table (Idx).To
2781 then
2782 Sloc_T := SCO_Raw_Table.Table (Idx).To;
2783 end if;
2785 if SCO_Raw_Table.Table (Idx).C1 = ' ' then
2787 -- This is a condition: nothing special to do
2789 Idx := Idx + 1;
2791 elsif SCO_Raw_Table.Table (Idx).C1 = '!' then
2793 -- The "not" operator has only one operand
2795 Idx := Idx + 1;
2796 Process_One;
2798 else
2799 -- This is an AND THEN or OR ELSE logical operator: follow the
2800 -- left, then the right operands.
2802 Idx := Idx + 1;
2804 Process_One;
2805 Process_One;
2806 end if;
2807 end Process_One;
2809 -- Start of processing for Compute_Range
2811 begin
2812 Process_One;
2813 From := Sloc_F;
2814 To := Sloc_T;
2815 end Compute_Range;
2817 -----------------
2818 -- Is_Decision --
2819 -----------------
2821 function Is_Decision (Idx : Nat) return Boolean is
2822 Index : Nat := Idx;
2824 begin
2825 loop
2826 declare
2827 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
2829 begin
2830 case T.C1 is
2831 when ' ' =>
2832 return False;
2834 when '!' =>
2836 -- This is a decision iff the only operand of the NOT
2837 -- operator could be a standalone decision.
2839 Index := Idx + 1;
2841 when others =>
2843 -- This node is a logical operator (and thus could be a
2844 -- standalone decision) iff it is a short circuit
2845 -- operator.
2847 return T.C2 /= '?';
2848 end case;
2849 end;
2850 end loop;
2851 end Is_Decision;
2853 -------------------------------
2854 -- Process_Pending_Decisions --
2855 -------------------------------
2857 procedure Process_Pending_Decisions
2858 (Original_Decision : SCO_Table_Entry)
2860 begin
2861 for Index in 1 .. Pending_Decisions.Last loop
2862 declare
2863 D : Decision renames Pending_Decisions.Table (Index);
2864 Idx : Nat := D.Top;
2866 begin
2867 -- Add a SCO table entry for the decision itself
2869 pragma Assert (D.Kind /= ' ');
2871 SCO_Table.Append
2872 ((To => No_Source_Location,
2873 From => D.Sloc,
2874 C1 => D.Kind,
2875 C2 => ' ',
2876 Last => False,
2877 Pragma_Sloc => Original_Decision.Pragma_Sloc,
2878 Pragma_Aspect_Name =>
2879 Original_Decision.Pragma_Aspect_Name));
2881 -- Then add ones for its nested operators/operands. Do not
2882 -- forget to tag its *last* entry as such.
2884 Add_Expression_Tree (Idx);
2885 SCO_Table.Table (SCO_Table.Last).Last := True;
2886 end;
2887 end loop;
2889 -- Clear the pending decisions list
2890 Pending_Decisions.Set_Last (0);
2891 end Process_Pending_Decisions;
2893 -----------------------------
2894 -- Search_Nested_Decisions --
2895 -----------------------------
2897 procedure Search_Nested_Decisions (Idx : in out Nat) is
2898 begin
2899 loop
2900 declare
2901 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2903 begin
2904 case T.C1 is
2905 when ' ' =>
2906 Idx := Idx + 1;
2907 exit;
2909 when '!' =>
2910 Collect_Decisions
2911 ((Kind => 'X',
2912 Sloc => T.From,
2913 Top => Idx),
2914 Idx);
2915 exit;
2917 when others =>
2918 if T.C2 = '?' then
2920 -- This is not a logical operator: start looking for
2921 -- nested decisions from here. Recurse over the left
2922 -- child and let the loop take care of the right one.
2924 Idx := Idx + 1;
2925 Search_Nested_Decisions (Idx);
2927 else
2928 -- We found a nested decision
2930 Collect_Decisions
2931 ((Kind => 'X',
2932 Sloc => T.From,
2933 Top => Idx),
2934 Idx);
2935 exit;
2936 end if;
2937 end case;
2938 end;
2939 end loop;
2940 end Search_Nested_Decisions;
2942 -------------------
2943 -- Skip_Decision --
2944 -------------------
2946 procedure Skip_Decision
2947 (Idx : in out Nat;
2948 Process_Nested_Decisions : Boolean)
2950 begin
2951 loop
2952 declare
2953 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2955 begin
2956 Idx := Idx + 1;
2958 case T.C1 is
2959 when ' ' =>
2960 exit;
2962 when '!' =>
2964 -- This NOT operator belongs to the outside decision:
2965 -- just skip it.
2967 null;
2969 when others =>
2970 if T.C2 = '?' and then Process_Nested_Decisions then
2972 -- This is not a logical operator: start looking for
2973 -- nested decisions from here. Recurse over the left
2974 -- child and let the loop take care of the right one.
2976 Search_Nested_Decisions (Idx);
2978 else
2979 -- This is a logical operator, so it belongs to the
2980 -- outside decision: skip its left child, then let the
2981 -- loop take care of the right one.
2983 Skip_Decision (Idx, Process_Nested_Decisions);
2984 end if;
2985 end case;
2986 end;
2987 end loop;
2988 end Skip_Decision;
2990 -- Start of processing for SCO_Record_Filtered
2992 begin
2993 -- Filtering must happen only once: do nothing if it this pass was
2994 -- already run.
2996 if SCO_Generation_State = Filtered then
2997 return;
2998 else
2999 pragma Assert (SCO_Generation_State = Raw);
3000 SCO_Generation_State := Filtered;
3001 end if;
3003 -- Loop through all SCO entries under SCO units
3005 for Unit_Idx in 1 .. SCO_Unit_Table.Last loop
3006 declare
3007 Unit : SCO_Unit_Table_Entry
3008 renames SCO_Unit_Table.Table (Unit_Idx);
3010 Idx : Nat := Unit.From;
3011 -- Index of the current SCO raw table entry
3013 New_From : constant Nat := SCO_Table.Last + 1;
3014 -- After copying SCO enties of interest to the final table, we
3015 -- will have to change the From/To indexes this unit targets.
3016 -- This constant keeps track of the new From index.
3018 begin
3019 while Idx <= Unit.To loop
3020 declare
3021 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
3023 begin
3024 case T.C1 is
3026 -- Decision (of any kind, including pragmas and aspects)
3028 when 'E' | 'G' | 'I' | 'W' | 'X' | 'P' | 'a' | 'A' =>
3029 if SCO_Pragma_Disabled (T.Pragma_Sloc) then
3031 -- Skip SCO entries for decisions in disabled
3032 -- constructs (pragmas or aspects).
3034 Idx := Idx + 1;
3035 Skip_Decision (Idx, False);
3037 else
3038 Collect_Decisions
3039 ((Kind => T.C1,
3040 Sloc => T.From,
3041 Top => Idx + 1),
3042 Idx);
3043 Process_Pending_Decisions (T);
3044 end if;
3046 -- There is no translation/filtering to do for other kind
3047 -- of SCO items (statements, dominance markers, etc.).
3049 when '|' | '&' | '!' | ' ' =>
3051 -- SCO logical operators and conditions cannot exist
3052 -- on their own: they must be inside a decision (such
3053 -- entries must have been skipped by
3054 -- Collect_Decisions).
3056 raise Program_Error;
3058 when others =>
3059 SCO_Table.Append (T);
3060 Idx := Idx + 1;
3061 end case;
3062 end;
3063 end loop;
3065 -- Now, update the SCO entry indexes in the unit entry
3067 Unit.From := New_From;
3068 Unit.To := SCO_Table.Last;
3069 end;
3070 end loop;
3072 -- Then clear the raw table to free bytes
3074 SCO_Raw_Table.Free;
3075 end SCO_Record_Filtered;
3077 end Par_SCO;