Add assember CFI directives to millicode division and remainder routines.
[official-gcc.git] / gcc / ada / par_sco.adb
blobc3aa2a5936e6829737d8bf1a0ea6010b6c66d270
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).
403 ----------------
404 -- Check_Node --
405 ----------------
407 function Check_Node (N : Node_Id) return Traverse_Result is
408 begin
409 -- If we are not sure this is a logical operator (AND and OR may be
410 -- turned into logical operators with the Short_Circuit_And_Or
411 -- pragma), assume it is. Putative decisions will be discarded if
412 -- needed in the secord pass.
414 if Is_Logical_Operator (N) /= False
415 or else Nkind (N) = N_If_Expression
416 then
417 return Abandon;
418 else
419 return OK;
420 end if;
421 end Check_Node;
423 function Traverse is new Traverse_Func (Check_Node);
425 -- Start of processing for Has_Decision
427 begin
428 return Traverse (N) = Abandon;
429 end Has_Decision;
431 ----------
432 -- Hash --
433 ----------
435 function Hash (F : Source_Ptr) return Header_Num is
436 begin
437 return Header_Num (Nat (F) mod 997);
438 end Hash;
440 ----------------
441 -- Initialize --
442 ----------------
444 procedure Initialize is
445 begin
446 SCO_Unit_Number_Table.Init;
448 -- The SCO_Unit_Number_Table entry with index 0 is intentionally set
449 -- aside to be used as temporary for sorting.
451 SCO_Unit_Number_Table.Increment_Last;
452 end Initialize;
454 -------------------------
455 -- Is_Logical_Operator --
456 -------------------------
458 function Is_Logical_Operator (N : Node_Id) return Tristate is
459 begin
460 if Nkind (N) in N_And_Then | N_Op_Not | N_Or_Else then
461 return True;
462 elsif Nkind (N) in N_Op_And | N_Op_Or then
463 return Unknown;
464 else
465 return False;
466 end if;
467 end Is_Logical_Operator;
469 -----------------------
470 -- Process_Decisions --
471 -----------------------
473 -- Version taking a list
475 procedure Process_Decisions
476 (L : List_Id;
477 T : Character;
478 Pragma_Sloc : Source_Ptr)
480 N : Node_Id;
482 begin
483 N := First (L);
484 while Present (N) loop
485 Process_Decisions (N, T, Pragma_Sloc);
486 Next (N);
487 end loop;
488 end Process_Decisions;
490 -- Version taking a node
492 Current_Pragma_Sloc : Source_Ptr := No_Location;
493 -- While processing a pragma, this is set to the sloc of the N_Pragma node
495 procedure Process_Decisions
496 (N : Node_Id;
497 T : Character;
498 Pragma_Sloc : Source_Ptr)
500 Mark : Nat;
501 -- This is used to mark the location of a decision sequence in the SCO
502 -- table. We use it for backing out a simple decision in an expression
503 -- context that contains only NOT operators.
505 Mark_Hash : Nat;
506 -- Likewise for the putative SCO_Raw_Hash_Table entries: see below
508 type Hash_Entry is record
509 Sloc : Source_Ptr;
510 SCO_Index : Nat;
511 end record;
512 -- We must register all conditions/pragmas in SCO_Raw_Hash_Table.
513 -- However we cannot register them in the same time we are adding the
514 -- corresponding SCO entries to the raw table since we may discard them
515 -- later on. So instead we put all putative conditions into Hash_Entries
516 -- (see below) and register them once we are sure we keep them.
518 -- This data structure holds the conditions/pragmas to register in
519 -- SCO_Raw_Hash_Table.
521 package Hash_Entries is new Table.Table
522 (Table_Component_Type => Hash_Entry,
523 Table_Index_Type => Nat,
524 Table_Low_Bound => 1,
525 Table_Initial => 10,
526 Table_Increment => 10,
527 Table_Name => "Hash_Entries");
528 -- Hold temporarily (i.e. free'd before returning) the Hash_Entry before
529 -- they are registered in SCO_Raw_Hash_Table.
531 X_Not_Decision : Boolean;
532 -- This flag keeps track of whether a decision sequence in the SCO table
533 -- contains only NOT operators, and is for an expression context (T=X).
534 -- The flag will be set False if T is other than X, or if an operator
535 -- other than NOT is in the sequence.
537 procedure Output_Decision_Operand (N : Node_Id);
538 -- The node N is the top level logical operator of a decision, or it is
539 -- one of the operands of a logical operator belonging to a single
540 -- complex decision. This routine outputs the sequence of table entries
541 -- corresponding to the node. Note that we do not process the sub-
542 -- operands to look for further decisions, that processing is done in
543 -- Process_Decision_Operand, because we can't get decisions mixed up in
544 -- the global table. Call has no effect if N is Empty.
546 procedure Output_Element (N : Node_Id);
547 -- Node N is an operand of a logical operator that is not itself a
548 -- logical operator, or it is a simple decision. This routine outputs
549 -- the table entry for the element, with C1 set to ' '. Last is set
550 -- False, and an entry is made in the condition hash table.
552 procedure Output_Header (T : Character);
553 -- Outputs a decision header node. T is I/W/E/P for IF/WHILE/EXIT WHEN/
554 -- PRAGMA, and 'X' for the expression case.
556 procedure Process_Decision_Operand (N : Node_Id);
557 -- This is called on node N, the top level node of a decision, or on one
558 -- of its operands or suboperands after generating the full output for
559 -- the complex decision. It process the suboperands of the decision
560 -- looking for nested decisions.
562 function Process_Node (N : Node_Id) return Traverse_Result;
563 -- Processes one node in the traversal, looking for logical operators,
564 -- and if one is found, outputs the appropriate table entries.
566 -----------------------------
567 -- Output_Decision_Operand --
568 -----------------------------
570 procedure Output_Decision_Operand (N : Node_Id) is
571 C1 : Character;
572 C2 : Character;
573 -- C1 holds a character that identifies the operation while C2
574 -- indicates whether we are sure (' ') or not ('?') this operation
575 -- belongs to the decision. '?' entries will be filtered out in the
576 -- second (SCO_Record_Filtered) pass.
578 L : Node_Id;
579 T : Tristate;
581 begin
582 if No (N) then
583 return;
584 end if;
586 T := Is_Logical_Operator (N);
588 -- Logical operator
590 if T /= False then
591 if Nkind (N) = N_Op_Not then
592 C1 := '!';
593 L := Empty;
595 else
596 L := Left_Opnd (N);
598 if Nkind (N) in N_Op_Or | N_Or_Else then
599 C1 := '|';
600 else pragma Assert (Nkind (N) in N_Op_And | N_And_Then);
601 C1 := '&';
602 end if;
603 end if;
605 if T = True then
606 C2 := ' ';
607 else
608 C2 := '?';
609 end if;
611 Set_Raw_Table_Entry
612 (C1 => C1,
613 C2 => C2,
614 From => Sloc (N),
615 To => No_Location,
616 Last => False);
618 Hash_Entries.Append ((Sloc (N), SCO_Raw_Table.Last));
620 Output_Decision_Operand (L);
621 Output_Decision_Operand (Right_Opnd (N));
623 -- Not a logical operator
625 else
626 Output_Element (N);
627 end if;
628 end Output_Decision_Operand;
630 --------------------
631 -- Output_Element --
632 --------------------
634 procedure Output_Element (N : Node_Id) is
635 FSloc : Source_Ptr;
636 LSloc : Source_Ptr;
637 begin
638 Sloc_Range (N, FSloc, LSloc);
639 Set_Raw_Table_Entry
640 (C1 => ' ',
641 C2 => 'c',
642 From => FSloc,
643 To => LSloc,
644 Last => False);
645 Hash_Entries.Append ((FSloc, SCO_Raw_Table.Last));
646 end Output_Element;
648 -------------------
649 -- Output_Header --
650 -------------------
652 procedure Output_Header (T : Character) is
653 Loc : Source_Ptr := No_Location;
654 -- Node whose Sloc is used for the decision
656 Nam : Name_Id := No_Name;
657 -- For the case of an aspect, aspect name
659 begin
660 case T is
661 when 'I' | 'E' | 'W' | 'a' | 'A' =>
663 -- For IF, EXIT, WHILE, or aspects, the token SLOC is that of
664 -- the parent of the expression.
666 Loc := Sloc (Parent (N));
668 if T = 'a' or else T = 'A' then
669 Nam := Chars (Identifier (Parent (N)));
670 end if;
672 when 'G' | 'P' =>
674 -- For entry guard, the token sloc is from the N_Entry_Body.
675 -- For PRAGMA, we must get the location from the pragma node.
676 -- Argument N is the pragma argument, and we have to go up
677 -- two levels (through the pragma argument association) to
678 -- get to the pragma node itself. For the guard on a select
679 -- alternative, we do not have access to the token location for
680 -- the WHEN, so we use the first sloc of the condition itself.
681 -- First_Sloc gives the most sensible result, but we have to
682 -- beware of also using it when computing the dominance marker
683 -- sloc (in the Set_Statement_Entry procedure), as this is not
684 -- fully equivalent to the "To" sloc computed by
685 -- Sloc_Range (Guard, To, From).
687 if Nkind (Parent (N)) in N_Accept_Alternative
688 | N_Delay_Alternative
689 | N_Terminate_Alternative
690 then
691 Loc := First_Sloc (N);
692 else
693 Loc := Sloc (Parent (Parent (N)));
694 end if;
696 when 'X' =>
698 -- For an expression, no Sloc
700 null;
702 -- No other possibilities
704 when others =>
705 raise Program_Error;
706 end case;
708 Set_Raw_Table_Entry
709 (C1 => T,
710 C2 => ' ',
711 From => Loc,
712 To => No_Location,
713 Last => False,
714 Pragma_Sloc => Pragma_Sloc,
715 Pragma_Aspect_Name => Nam);
717 -- For an aspect specification, which will be rewritten into a
718 -- pragma, enter a hash table entry now.
720 if T = 'a' then
721 Hash_Entries.Append ((Loc, SCO_Raw_Table.Last));
722 end if;
723 end Output_Header;
725 ------------------------------
726 -- Process_Decision_Operand --
727 ------------------------------
729 procedure Process_Decision_Operand (N : Node_Id) is
730 begin
731 if Is_Logical_Operator (N) /= False then
732 if Nkind (N) /= N_Op_Not then
733 Process_Decision_Operand (Left_Opnd (N));
734 X_Not_Decision := False;
735 end if;
737 Process_Decision_Operand (Right_Opnd (N));
739 else
740 Process_Decisions (N, 'X', Pragma_Sloc);
741 end if;
742 end Process_Decision_Operand;
744 ------------------
745 -- Process_Node --
746 ------------------
748 function Process_Node (N : Node_Id) return Traverse_Result is
749 begin
750 case Nkind (N) is
752 -- Logical operators, output table entries and then process
753 -- operands recursively to deal with nested conditions.
755 when N_And_Then
756 | N_Op_And
757 | N_Op_Not
758 | N_Op_Or
759 | N_Or_Else
761 declare
762 T : Character;
764 begin
765 -- If outer level, then type comes from call, otherwise it
766 -- is more deeply nested and counts as X for expression.
768 if N = Process_Decisions.N then
769 T := Process_Decisions.T;
770 else
771 T := 'X';
772 end if;
774 -- Output header for sequence
776 X_Not_Decision := T = 'X' and then Nkind (N) = N_Op_Not;
777 Mark := SCO_Raw_Table.Last;
778 Mark_Hash := Hash_Entries.Last;
779 Output_Header (T);
781 -- Output the decision
783 Output_Decision_Operand (N);
785 -- If the decision was in an expression context (T = 'X')
786 -- and contained only NOT operators, then we don't output
787 -- it, so delete it.
789 if X_Not_Decision then
790 SCO_Raw_Table.Set_Last (Mark);
791 Hash_Entries.Set_Last (Mark_Hash);
793 -- Otherwise, set Last in last table entry to mark end
795 else
796 SCO_Raw_Table.Table (SCO_Raw_Table.Last).Last := True;
797 end if;
799 -- Process any embedded decisions
801 Process_Decision_Operand (N);
802 return Skip;
803 end;
805 -- Case expression
807 -- Really hard to believe this is correct given the special
808 -- handling for if expressions below ???
810 when N_Case_Expression =>
811 return OK; -- ???
813 -- If expression, processed like an if statement
815 when N_If_Expression =>
816 declare
817 Cond : constant Node_Id := First (Expressions (N));
818 Thnx : constant Node_Id := Next (Cond);
819 Elsx : constant Node_Id := Next (Thnx);
821 begin
822 Process_Decisions (Cond, 'I', Pragma_Sloc);
823 Process_Decisions (Thnx, 'X', Pragma_Sloc);
824 Process_Decisions (Elsx, 'X', Pragma_Sloc);
825 return Skip;
826 end;
828 when N_Quantified_Expression =>
829 declare
830 Cond : constant Node_Id := Condition (N);
831 begin
832 Process_Decisions (Cond, 'W', Pragma_Sloc);
833 return Skip;
834 end;
836 -- All other cases, continue scan
838 when others =>
839 return OK;
840 end case;
841 end Process_Node;
843 procedure Traverse is new Traverse_Proc (Process_Node);
845 -- Start of processing for Process_Decisions
847 begin
848 if No (N) then
849 return;
850 end if;
852 Hash_Entries.Init;
854 -- See if we have simple decision at outer level and if so then
855 -- generate the decision entry for this simple decision. A simple
856 -- decision is a boolean expression (which is not a logical operator
857 -- or short circuit form) appearing as the operand of an IF, WHILE,
858 -- EXIT WHEN, or special PRAGMA construct.
860 if T /= 'X' and then Is_Logical_Operator (N) = False then
861 Output_Header (T);
862 Output_Element (N);
864 -- Change Last in last table entry to True to mark end of
865 -- sequence, which is this case is only one element long.
867 SCO_Raw_Table.Table (SCO_Raw_Table.Last).Last := True;
868 end if;
870 Traverse (N);
872 -- Now we have the definitive set of SCO entries, register them in the
873 -- corresponding hash table.
875 for J in 1 .. Hash_Entries.Last loop
876 SCO_Raw_Hash_Table.Set
877 (Hash_Entries.Table (J).Sloc,
878 Hash_Entries.Table (J).SCO_Index);
879 end loop;
881 Hash_Entries.Free;
882 end Process_Decisions;
884 -----------
885 -- pscos --
886 -----------
888 procedure pscos is
889 procedure Write_Info_Char (C : Character) renames Write_Char;
890 -- Write one character;
892 procedure Write_Info_Initiate (Key : Character) renames Write_Char;
893 -- Start new one and write one character;
895 procedure Write_Info_Nat (N : Nat);
896 -- Write value of N
898 procedure Write_Info_Terminate renames Write_Eol;
899 -- Terminate current line
901 --------------------
902 -- Write_Info_Nat --
903 --------------------
905 procedure Write_Info_Nat (N : Nat) is
906 begin
907 Write_Int (N);
908 end Write_Info_Nat;
910 procedure Debug_Put_SCOs is new Put_SCOs;
912 -- Start of processing for pscos
914 begin
915 Debug_Put_SCOs;
916 end pscos;
918 ---------------------
919 -- Record_Instance --
920 ---------------------
922 procedure Record_Instance (Id : Instance_Id; Inst_Sloc : Source_Ptr) is
923 Inst_Src : constant Source_File_Index :=
924 Get_Source_File_Index (Inst_Sloc);
925 begin
926 SCO_Instance_Table.Append
927 ((Inst_Dep_Num => Dependency_Num (Unit (Inst_Src)),
928 Inst_Loc => To_Source_Location (Inst_Sloc),
929 Enclosing_Instance => SCO_Instance_Index (Instance (Inst_Src))));
931 pragma Assert
932 (SCO_Instance_Table.Last = SCO_Instance_Index (Id));
933 end Record_Instance;
935 ----------------
936 -- SCO_Output --
937 ----------------
939 procedure SCO_Output is
940 procedure Populate_SCO_Instance_Table is
941 new Sinput.Iterate_On_Instances (Record_Instance);
943 begin
944 pragma Assert (SCO_Generation_State = Filtered);
946 if Debug_Flag_Dot_OO then
947 dsco;
948 end if;
950 Populate_SCO_Instance_Table;
952 -- Sort the unit tables based on dependency numbers
954 Unit_Table_Sort : declare
955 function Lt (Op1 : Natural; Op2 : Natural) return Boolean;
956 -- Comparison routine for sort call
958 procedure Move (From : Natural; To : Natural);
959 -- Move routine for sort call
961 --------
962 -- Lt --
963 --------
965 function Lt (Op1 : Natural; Op2 : Natural) return Boolean is
966 begin
967 return
968 Dependency_Num
969 (SCO_Unit_Number_Table.Table (SCO_Unit_Index (Op1)))
971 Dependency_Num
972 (SCO_Unit_Number_Table.Table (SCO_Unit_Index (Op2)));
973 end Lt;
975 ----------
976 -- Move --
977 ----------
979 procedure Move (From : Natural; To : Natural) is
980 begin
981 SCO_Unit_Table.Table (SCO_Unit_Index (To)) :=
982 SCO_Unit_Table.Table (SCO_Unit_Index (From));
983 SCO_Unit_Number_Table.Table (SCO_Unit_Index (To)) :=
984 SCO_Unit_Number_Table.Table (SCO_Unit_Index (From));
985 end Move;
987 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
989 -- Start of processing for Unit_Table_Sort
991 begin
992 Sorting.Sort (Integer (SCO_Unit_Table.Last));
993 end Unit_Table_Sort;
995 -- Loop through entries in the unit table to set file name and
996 -- dependency number entries.
998 for J in 1 .. SCO_Unit_Table.Last loop
999 declare
1000 U : constant Unit_Number_Type := SCO_Unit_Number_Table.Table (J);
1001 UTE : SCO_Unit_Table_Entry renames SCO_Unit_Table.Table (J);
1003 begin
1004 Get_Name_String (Reference_Name (Source_Index (U)));
1005 UTE.File_Name := new String'(Name_Buffer (1 .. Name_Len));
1006 UTE.Dep_Num := Dependency_Num (U);
1007 end;
1008 end loop;
1010 -- Now the tables are all setup for output to the ALI file
1012 Write_SCOs_To_ALI_File;
1013 end SCO_Output;
1015 -------------------------
1016 -- SCO_Pragma_Disabled --
1017 -------------------------
1019 function SCO_Pragma_Disabled (Loc : Source_Ptr) return Boolean is
1020 Index : Nat;
1022 begin
1023 if Loc = No_Location then
1024 return False;
1025 end if;
1027 Index := SCO_Raw_Hash_Table.Get (Loc);
1029 -- The test here for zero is to deal with possible previous errors, and
1030 -- for the case of pragma statement SCOs, for which we always set the
1031 -- Pragma_Sloc even if the particular pragma cannot be specifically
1032 -- disabled.
1034 if Index /= 0 then
1035 declare
1036 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1038 begin
1039 case T.C1 is
1040 when 'S' =>
1041 -- Pragma statement
1043 return T.C2 = 'p';
1045 when 'A' =>
1046 -- Aspect decision (enabled)
1048 return False;
1050 when 'a' =>
1051 -- Aspect decision (not enabled)
1053 return True;
1055 when ASCII.NUL =>
1056 -- Nullified disabled SCO
1058 return True;
1060 when others =>
1061 raise Program_Error;
1062 end case;
1063 end;
1065 else
1066 return False;
1067 end if;
1068 end SCO_Pragma_Disabled;
1070 --------------------
1071 -- SCO_Record_Raw --
1072 --------------------
1074 procedure SCO_Record_Raw (U : Unit_Number_Type) is
1075 procedure Traverse_Aux_Decls (N : Node_Id);
1076 -- Traverse the Aux_Decls_Node of compilation unit N
1078 ------------------------
1079 -- Traverse_Aux_Decls --
1080 ------------------------
1082 procedure Traverse_Aux_Decls (N : Node_Id) is
1083 ADN : constant Node_Id := Aux_Decls_Node (N);
1085 begin
1086 Traverse_Declarations_Or_Statements (Config_Pragmas (ADN));
1087 Traverse_Declarations_Or_Statements (Pragmas_After (ADN));
1089 -- Declarations and Actions do not correspond to source constructs,
1090 -- they contain only nodes from expansion, so at this point they
1091 -- should still be empty:
1093 pragma Assert (No (Declarations (ADN)));
1094 pragma Assert (No (Actions (ADN)));
1095 end Traverse_Aux_Decls;
1097 -- Local variables
1099 From : Nat;
1100 Lu : Node_Id;
1102 -- Start of processing for SCO_Record_Raw
1104 begin
1105 -- It is legitimate to run this pass multiple times (once per unit) so
1106 -- run it even if it was already run before.
1108 pragma Assert (SCO_Generation_State in None .. Raw);
1109 SCO_Generation_State := Raw;
1111 -- Ignore call if not generating code and generating SCO's
1113 if not (Generate_SCO and then Operating_Mode = Generate_Code) then
1114 return;
1115 end if;
1117 -- Ignore call if this unit already recorded
1119 for J in 1 .. SCO_Unit_Number_Table.Last loop
1120 if U = SCO_Unit_Number_Table.Table (J) then
1121 return;
1122 end if;
1123 end loop;
1125 -- Otherwise record starting entry
1127 From := SCO_Raw_Table.Last + 1;
1129 -- Get Unit (checking case of subunit)
1131 Lu := Unit (Cunit (U));
1133 if Nkind (Lu) = N_Subunit then
1134 Lu := Proper_Body (Lu);
1135 end if;
1137 -- Traverse the unit
1139 Traverse_Aux_Decls (Cunit (U));
1141 case Nkind (Lu) is
1142 when N_Generic_Instantiation
1143 | N_Generic_Package_Declaration
1144 | N_Package_Body
1145 | N_Package_Declaration
1146 | N_Protected_Body
1147 | N_Subprogram_Body
1148 | N_Subprogram_Declaration
1149 | N_Task_Body
1151 Traverse_Declarations_Or_Statements (L => No_List, P => Lu);
1153 -- All other cases of compilation units (e.g. renamings), generate no
1154 -- SCO information.
1156 when others =>
1157 null;
1158 end case;
1160 -- Make entry for new unit in unit tables, we will fill in the file
1161 -- name and dependency numbers later.
1163 SCO_Unit_Table.Append (
1164 (Dep_Num => 0,
1165 File_Name => null,
1166 File_Index => Get_Source_File_Index (Sloc (Lu)),
1167 From => From,
1168 To => SCO_Raw_Table.Last));
1170 SCO_Unit_Number_Table.Append (U);
1171 end SCO_Record_Raw;
1173 -----------------------
1174 -- Set_SCO_Condition --
1175 -----------------------
1177 procedure Set_SCO_Condition (Cond : Node_Id; Val : Boolean) is
1179 -- SCO annotations are not processed after the filtering pass
1181 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1183 Constant_Condition_Code : constant array (Boolean) of Character :=
1184 (False => 'f', True => 't');
1186 Orig : constant Node_Id := Original_Node (Cond);
1187 Dummy : Source_Ptr;
1188 Index : Nat;
1189 Start : Source_Ptr;
1191 begin
1192 Sloc_Range (Orig, Start, Dummy);
1193 Index := SCO_Raw_Hash_Table.Get (Start);
1195 -- Index can be zero for boolean expressions that do not have SCOs
1196 -- (simple decisions outside of a control flow structure), or in case
1197 -- of a previous error.
1199 if Index = 0 then
1200 return;
1202 else
1203 pragma Assert (SCO_Raw_Table.Table (Index).C1 = ' ');
1204 SCO_Raw_Table.Table (Index).C2 := Constant_Condition_Code (Val);
1205 end if;
1206 end Set_SCO_Condition;
1208 ------------------------------
1209 -- Set_SCO_Logical_Operator --
1210 ------------------------------
1212 procedure Set_SCO_Logical_Operator (Op : Node_Id) is
1214 -- SCO annotations are not processed after the filtering pass
1216 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1218 Orig : constant Node_Id := Original_Node (Op);
1219 Orig_Sloc : constant Source_Ptr := Sloc (Orig);
1220 Index : constant Nat := SCO_Raw_Hash_Table.Get (Orig_Sloc);
1222 begin
1223 -- All (putative) logical operators are supposed to have their own entry
1224 -- in the SCOs table. However, the semantic analysis may invoke this
1225 -- subprogram with nodes that are out of the SCO generation scope.
1227 if Index /= 0 then
1228 SCO_Raw_Table.Table (Index).C2 := ' ';
1229 end if;
1230 end Set_SCO_Logical_Operator;
1232 ----------------------------
1233 -- Set_SCO_Pragma_Enabled --
1234 ----------------------------
1236 procedure Set_SCO_Pragma_Enabled (Loc : Source_Ptr) is
1238 -- SCO annotations are not processed after the filtering pass
1240 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1242 Index : Nat;
1244 begin
1245 -- Nothing to do if not generating SCO, or if we're not processing the
1246 -- original source occurrence of the pragma.
1248 if not (Generate_SCO
1249 and then In_Extended_Main_Source_Unit (Loc)
1250 and then not (In_Instance or In_Inlined_Body))
1251 then
1252 return;
1253 end if;
1255 -- Note: the reason we use the Sloc value as the key is that in the
1256 -- generic case, the call to this procedure is made on a copy of the
1257 -- original node, so we can't use the Node_Id value.
1259 Index := SCO_Raw_Hash_Table.Get (Loc);
1261 -- A zero index here indicates that semantic analysis found an
1262 -- activated pragma at Loc which does not have a corresponding pragma
1263 -- or aspect at the syntax level. This may occur in legitimate cases
1264 -- because of expanded code (such are Pre/Post conditions generated for
1265 -- formal parameter validity checks), or as a consequence of a previous
1266 -- error.
1268 if Index = 0 then
1269 return;
1271 else
1272 declare
1273 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1275 begin
1276 -- Note: may be called multiple times for the same sloc, so
1277 -- account for the fact that the entry may already have been
1278 -- marked enabled.
1280 case T.C1 is
1281 -- Aspect (decision SCO)
1283 when 'a' =>
1284 T.C1 := 'A';
1286 when 'A' =>
1287 null;
1289 -- Pragma (statement SCO)
1291 when 'S' =>
1292 pragma Assert (T.C2 = 'p' or else T.C2 = 'P');
1293 T.C2 := 'P';
1295 when others =>
1296 raise Program_Error;
1297 end case;
1298 end;
1299 end if;
1300 end Set_SCO_Pragma_Enabled;
1302 -------------------------
1303 -- Set_Raw_Table_Entry --
1304 -------------------------
1306 procedure Set_Raw_Table_Entry
1307 (C1 : Character;
1308 C2 : Character;
1309 From : Source_Ptr;
1310 To : Source_Ptr;
1311 Last : Boolean;
1312 Pragma_Sloc : Source_Ptr := No_Location;
1313 Pragma_Aspect_Name : Name_Id := No_Name)
1315 pragma Assert (SCO_Generation_State = Raw);
1316 begin
1317 SCO_Raw_Table.Append
1318 ((C1 => C1,
1319 C2 => C2,
1320 From => To_Source_Location (From),
1321 To => To_Source_Location (To),
1322 Last => Last,
1323 Pragma_Sloc => Pragma_Sloc,
1324 Pragma_Aspect_Name => Pragma_Aspect_Name));
1325 end Set_Raw_Table_Entry;
1327 ------------------------
1328 -- To_Source_Location --
1329 ------------------------
1331 function To_Source_Location (S : Source_Ptr) return Source_Location is
1332 begin
1333 if S = No_Location then
1334 return No_Source_Location;
1335 else
1336 return
1337 (Line => Get_Logical_Line_Number (S),
1338 Col => Get_Column_Number (S));
1339 end if;
1340 end To_Source_Location;
1342 -----------------------------------------
1343 -- Traverse_Declarations_Or_Statements --
1344 -----------------------------------------
1346 -- Tables used by Traverse_Declarations_Or_Statements for temporarily
1347 -- holding statement and decision entries. These are declared globally
1348 -- since they are shared by recursive calls to this procedure.
1350 type SC_Entry is record
1351 N : Node_Id;
1352 From : Source_Ptr;
1353 To : Source_Ptr;
1354 Typ : Character;
1355 end record;
1356 -- Used to store a single entry in the following table, From:To represents
1357 -- the range of entries in the CS line entry, and typ is the type, with
1358 -- space meaning that no type letter will accompany the entry.
1360 package SC is new Table.Table
1361 (Table_Component_Type => SC_Entry,
1362 Table_Index_Type => Nat,
1363 Table_Low_Bound => 1,
1364 Table_Initial => 1000,
1365 Table_Increment => 200,
1366 Table_Name => "SCO_SC");
1367 -- Used to store statement components for a CS entry to be output as a
1368 -- result of the call to this procedure. SC.Last is the last entry stored,
1369 -- so the current statement sequence is represented by SC_Array (SC_First
1370 -- .. SC.Last), where SC_First is saved on entry to each recursive call to
1371 -- the routine.
1373 -- Extend_Statement_Sequence adds an entry to this array, and then
1374 -- Set_Statement_Entry clears the entries starting with SC_First, copying
1375 -- these entries to the main SCO output table. The reason that we do the
1376 -- temporary caching of results in this array is that we want the SCO table
1377 -- entries for a given CS line to be contiguous, and the processing may
1378 -- output intermediate entries such as decision entries.
1380 type SD_Entry is record
1381 Nod : Node_Id;
1382 Lst : List_Id;
1383 Typ : Character;
1384 Plo : Source_Ptr;
1385 end record;
1386 -- Used to store a single entry in the following table. Nod is the node to
1387 -- be searched for decisions for the case of Process_Decisions_Defer with a
1388 -- node argument (with Lst set to No_List. Lst is the list to be searched
1389 -- for decisions for the case of Process_Decisions_Defer with a List
1390 -- argument (in which case Nod is set to Empty). Plo is the sloc of the
1391 -- enclosing pragma, if any.
1393 package SD is new Table.Table
1394 (Table_Component_Type => SD_Entry,
1395 Table_Index_Type => Nat,
1396 Table_Low_Bound => 1,
1397 Table_Initial => 1000,
1398 Table_Increment => 200,
1399 Table_Name => "SCO_SD");
1400 -- Used to store possible decision information. Instead of calling the
1401 -- Process_Decisions procedures directly, we call Process_Decisions_Defer,
1402 -- which simply stores the arguments in this table. Then when we clear
1403 -- out a statement sequence using Set_Statement_Entry, after generating
1404 -- the CS lines for the statements, the entries in this table result in
1405 -- calls to Process_Decision. The reason for doing things this way is to
1406 -- ensure that decisions are output after the CS line for the statements
1407 -- in which the decisions occur.
1409 procedure Traverse_Declarations_Or_Statements
1410 (L : List_Id;
1411 D : Dominant_Info := No_Dominant;
1412 P : Node_Id := Empty)
1414 Discard_Dom : Dominant_Info;
1415 pragma Warnings (Off, Discard_Dom);
1416 begin
1417 Discard_Dom := Traverse_Declarations_Or_Statements (L, D, P);
1418 end Traverse_Declarations_Or_Statements;
1420 function Traverse_Declarations_Or_Statements
1421 (L : List_Id;
1422 D : Dominant_Info := No_Dominant;
1423 P : Node_Id := Empty) return Dominant_Info
1425 Current_Dominant : Dominant_Info := D;
1426 -- Dominance information for the current basic block
1428 Current_Test : Node_Id;
1429 -- Conditional node (N_If_Statement or N_Elsif being processed)
1431 N : Node_Id;
1433 SC_First : constant Nat := SC.Last + 1;
1434 SD_First : constant Nat := SD.Last + 1;
1435 -- Record first entries used in SC/SD at this recursive level
1437 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character);
1438 -- Extend the current statement sequence to encompass the node N. Typ is
1439 -- the letter that identifies the type of statement/declaration that is
1440 -- being added to the sequence.
1442 procedure Process_Decisions_Defer (N : Node_Id; T : Character);
1443 pragma Inline (Process_Decisions_Defer);
1444 -- This routine is logically the same as Process_Decisions, except that
1445 -- the arguments are saved in the SD table for later processing when
1446 -- Set_Statement_Entry is called, which goes through the saved entries
1447 -- making the corresponding calls to Process_Decision. Note: the
1448 -- enclosing statement must have already been added to the current
1449 -- statement sequence, so that nested decisions are properly
1450 -- identified as such.
1452 procedure Process_Decisions_Defer (L : List_Id; T : Character);
1453 pragma Inline (Process_Decisions_Defer);
1454 -- Same case for list arguments, deferred call to Process_Decisions
1456 procedure Set_Statement_Entry;
1457 -- Output CS entries for all statements saved in table SC, and end the
1458 -- current CS sequence. Then output entries for all decisions nested in
1459 -- these statements, which have been deferred so far.
1461 procedure Traverse_One (N : Node_Id);
1462 -- Traverse one declaration or statement
1464 procedure Traverse_Aspects (N : Node_Id);
1465 -- Helper for Traverse_One: traverse N's aspect specifications
1467 procedure Traverse_Degenerate_Subprogram (N : Node_Id);
1468 -- Common code to handle null procedures and expression functions. Emit
1469 -- a SCO of the given Kind and N outside of the dominance flow.
1471 -------------------------------
1472 -- Extend_Statement_Sequence --
1473 -------------------------------
1475 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character) is
1476 Dummy : Source_Ptr;
1477 F : Source_Ptr;
1478 T : Source_Ptr;
1479 To_Node : Node_Id := Empty;
1481 begin
1482 Sloc_Range (N, F, T);
1484 case Nkind (N) is
1485 when N_Accept_Statement =>
1486 if Present (Parameter_Specifications (N)) then
1487 To_Node := Last (Parameter_Specifications (N));
1488 elsif Present (Entry_Index (N)) then
1489 To_Node := Entry_Index (N);
1490 else
1491 To_Node := Entry_Direct_Name (N);
1492 end if;
1494 when N_Case_Statement =>
1495 To_Node := Expression (N);
1497 when N_Elsif_Part
1498 | N_If_Statement
1500 To_Node := Condition (N);
1502 when N_Extended_Return_Statement =>
1503 To_Node := Last (Return_Object_Declarations (N));
1505 when N_Loop_Statement =>
1506 To_Node := Iteration_Scheme (N);
1508 when N_Asynchronous_Select
1509 | N_Conditional_Entry_Call
1510 | N_Selective_Accept
1511 | N_Single_Protected_Declaration
1512 | N_Single_Task_Declaration
1513 | N_Timed_Entry_Call
1515 T := F;
1517 when N_Protected_Type_Declaration
1518 | N_Task_Type_Declaration
1520 if Has_Aspects (N) then
1521 To_Node := Last (Aspect_Specifications (N));
1523 elsif Present (Discriminant_Specifications (N)) then
1524 To_Node := Last (Discriminant_Specifications (N));
1526 else
1527 To_Node := Defining_Identifier (N);
1528 end if;
1530 when N_Subexpr =>
1531 To_Node := N;
1533 when others =>
1534 null;
1535 end case;
1537 if Present (To_Node) then
1538 Sloc_Range (To_Node, Dummy, T);
1539 end if;
1541 SC.Append ((N, F, T, Typ));
1542 end Extend_Statement_Sequence;
1544 -----------------------------
1545 -- Process_Decisions_Defer --
1546 -----------------------------
1548 procedure Process_Decisions_Defer (N : Node_Id; T : Character) is
1549 begin
1550 SD.Append ((N, No_List, T, Current_Pragma_Sloc));
1551 end Process_Decisions_Defer;
1553 procedure Process_Decisions_Defer (L : List_Id; T : Character) is
1554 begin
1555 SD.Append ((Empty, L, T, Current_Pragma_Sloc));
1556 end Process_Decisions_Defer;
1558 -------------------------
1559 -- Set_Statement_Entry --
1560 -------------------------
1562 procedure Set_Statement_Entry is
1563 SC_Last : constant Int := SC.Last;
1564 SD_Last : constant Int := SD.Last;
1566 begin
1567 -- Output statement entries from saved entries in SC table
1569 for J in SC_First .. SC_Last loop
1570 if J = SC_First then
1572 if Current_Dominant /= No_Dominant then
1573 declare
1574 From : Source_Ptr;
1575 To : Source_Ptr;
1577 begin
1578 Sloc_Range (Current_Dominant.N, From, To);
1580 if Current_Dominant.K /= 'E' then
1581 To := No_Location;
1582 end if;
1584 -- Be consistent with the location determined in
1585 -- Output_Header.
1587 if Current_Dominant.K = 'T'
1588 and then Nkind (Parent (Current_Dominant.N))
1589 in N_Accept_Alternative
1590 | N_Delay_Alternative
1591 | N_Terminate_Alternative
1592 then
1593 From := First_Sloc (Current_Dominant.N);
1594 end if;
1596 Set_Raw_Table_Entry
1597 (C1 => '>',
1598 C2 => Current_Dominant.K,
1599 From => From,
1600 To => To,
1601 Last => False,
1602 Pragma_Sloc => No_Location,
1603 Pragma_Aspect_Name => No_Name);
1604 end;
1605 end if;
1606 end if;
1608 declare
1609 SCE : SC_Entry renames SC.Table (J);
1610 Pragma_Sloc : Source_Ptr := No_Location;
1611 Pragma_Aspect_Name : Name_Id := No_Name;
1613 begin
1614 -- For the case of a statement SCO for a pragma controlled by
1615 -- Set_SCO_Pragma_Enabled, set Pragma_Sloc so that the SCO (and
1616 -- those of any nested decision) is emitted only if the pragma
1617 -- is enabled.
1619 if SCE.Typ = 'p' then
1620 Pragma_Sloc := SCE.From;
1621 SCO_Raw_Hash_Table.Set
1622 (Pragma_Sloc, SCO_Raw_Table.Last + 1);
1623 Pragma_Aspect_Name := Pragma_Name_Unmapped (SCE.N);
1624 pragma Assert (Pragma_Aspect_Name /= No_Name);
1626 elsif SCE.Typ = 'P' then
1627 Pragma_Aspect_Name := Pragma_Name_Unmapped (SCE.N);
1628 pragma Assert (Pragma_Aspect_Name /= No_Name);
1629 end if;
1631 Set_Raw_Table_Entry
1632 (C1 => 'S',
1633 C2 => SCE.Typ,
1634 From => SCE.From,
1635 To => SCE.To,
1636 Last => (J = SC_Last),
1637 Pragma_Sloc => Pragma_Sloc,
1638 Pragma_Aspect_Name => Pragma_Aspect_Name);
1639 end;
1640 end loop;
1642 -- Last statement of basic block, if present, becomes new current
1643 -- dominant.
1645 if SC_Last >= SC_First then
1646 Current_Dominant := ('S', SC.Table (SC_Last).N);
1647 end if;
1649 -- Clear out used section of SC table
1651 SC.Set_Last (SC_First - 1);
1653 -- Output any embedded decisions
1655 for J in SD_First .. SD_Last loop
1656 declare
1657 SDE : SD_Entry renames SD.Table (J);
1659 begin
1660 if Present (SDE.Nod) then
1661 Process_Decisions (SDE.Nod, SDE.Typ, SDE.Plo);
1662 else
1663 Process_Decisions (SDE.Lst, SDE.Typ, SDE.Plo);
1664 end if;
1665 end;
1666 end loop;
1668 -- Clear out used section of SD table
1670 SD.Set_Last (SD_First - 1);
1671 end Set_Statement_Entry;
1673 ----------------------
1674 -- Traverse_Aspects --
1675 ----------------------
1677 procedure Traverse_Aspects (N : Node_Id) is
1678 AE : Node_Id;
1679 AN : Node_Id;
1680 C1 : Character;
1682 begin
1683 AN := First (Aspect_Specifications (N));
1684 while Present (AN) loop
1685 AE := Expression (AN);
1687 -- SCOs are generated before semantic analysis/expansion:
1688 -- PPCs are not split yet.
1690 pragma Assert (not Split_PPC (AN));
1692 C1 := ASCII.NUL;
1694 case Get_Aspect_Id (AN) is
1696 -- Aspects rewritten into pragmas controlled by a Check_Policy:
1697 -- Current_Pragma_Sloc must be set to the sloc of the aspect
1698 -- specification. The corresponding pragma will have the same
1699 -- sloc. Note that Invariant, Pre, and Post will be enabled if
1700 -- the policy is Check; on the other hand, predicate aspects
1701 -- will be enabled for Check and Ignore (when Add_Predicate
1702 -- is called) because the actual checks occur in client units.
1703 -- When the assertion policy for Predicate is Disable, the
1704 -- SCO remains disabled, because Add_Predicate is never called.
1706 -- Pre/post can have checks in client units too because of
1707 -- inheritance, so should they receive the same treatment???
1709 when Aspect_Dynamic_Predicate
1710 | Aspect_Invariant
1711 | Aspect_Post
1712 | Aspect_Postcondition
1713 | Aspect_Pre
1714 | Aspect_Precondition
1715 | Aspect_Predicate
1716 | Aspect_Static_Predicate
1717 | Aspect_Type_Invariant
1719 C1 := 'a';
1721 -- Other aspects: just process any decision nested in the
1722 -- aspect expression.
1724 when others =>
1725 if Has_Decision (AE) then
1726 C1 := 'X';
1727 end if;
1728 end case;
1730 if C1 /= ASCII.NUL then
1731 pragma Assert (Current_Pragma_Sloc = No_Location);
1733 if C1 = 'a' or else C1 = 'A' then
1734 Current_Pragma_Sloc := Sloc (AN);
1735 end if;
1737 Process_Decisions_Defer (AE, C1);
1739 Current_Pragma_Sloc := No_Location;
1740 end if;
1742 Next (AN);
1743 end loop;
1744 end Traverse_Aspects;
1746 ------------------------------------
1747 -- Traverse_Degenerate_Subprogram --
1748 ------------------------------------
1750 procedure Traverse_Degenerate_Subprogram (N : Node_Id) is
1751 begin
1752 -- Complete current sequence of statements
1754 Set_Statement_Entry;
1756 declare
1757 Saved_Dominant : constant Dominant_Info := Current_Dominant;
1758 -- Save last statement in current sequence as dominant
1760 begin
1761 -- Output statement SCO for degenerate subprogram body (null
1762 -- statement or freestanding expression) outside of the dominance
1763 -- chain.
1765 Current_Dominant := No_Dominant;
1766 Extend_Statement_Sequence (N, Typ => 'X');
1768 -- For the case of an expression-function, collect decisions
1769 -- embedded in the expression now.
1771 if Nkind (N) in N_Subexpr then
1772 Process_Decisions_Defer (N, 'X');
1773 end if;
1775 Set_Statement_Entry;
1777 -- Restore current dominant information designating last statement
1778 -- in previous sequence (i.e. make the dominance chain skip over
1779 -- the degenerate body).
1781 Current_Dominant := Saved_Dominant;
1782 end;
1783 end Traverse_Degenerate_Subprogram;
1785 ------------------
1786 -- Traverse_One --
1787 ------------------
1789 procedure Traverse_One (N : Node_Id) is
1790 begin
1791 -- Initialize or extend current statement sequence. Note that for
1792 -- special cases such as IF and Case statements we will modify
1793 -- the range to exclude internal statements that should not be
1794 -- counted as part of the current statement sequence.
1796 case Nkind (N) is
1798 -- Package declaration
1800 when N_Package_Declaration =>
1801 Set_Statement_Entry;
1802 Traverse_Package_Declaration (N, Current_Dominant);
1804 -- Generic package declaration
1806 when N_Generic_Package_Declaration =>
1807 Set_Statement_Entry;
1808 Traverse_Generic_Package_Declaration (N);
1810 -- Package body
1812 when N_Package_Body =>
1813 Set_Statement_Entry;
1814 Traverse_Package_Body (N);
1816 -- Subprogram declaration or subprogram body stub
1818 when N_Expression_Function
1819 | N_Subprogram_Body_Stub
1820 | N_Subprogram_Declaration
1822 declare
1823 Spec : constant Node_Id := Specification (N);
1824 begin
1825 Process_Decisions_Defer
1826 (Parameter_Specifications (Spec), 'X');
1828 -- Case of a null procedure: generate SCO for fictitious
1829 -- NULL statement located at the NULL keyword in the
1830 -- procedure specification.
1832 if Nkind (N) = N_Subprogram_Declaration
1833 and then Nkind (Spec) = N_Procedure_Specification
1834 and then Null_Present (Spec)
1835 then
1836 Traverse_Degenerate_Subprogram (Null_Statement (Spec));
1838 -- Case of an expression function: generate a statement SCO
1839 -- for the expression (and then decision SCOs for any nested
1840 -- decisions).
1842 elsif Nkind (N) = N_Expression_Function then
1843 Traverse_Degenerate_Subprogram (Expression (N));
1844 end if;
1845 end;
1847 -- Entry declaration
1849 when N_Entry_Declaration =>
1850 Process_Decisions_Defer (Parameter_Specifications (N), 'X');
1852 -- Generic subprogram declaration
1854 when N_Generic_Subprogram_Declaration =>
1855 Process_Decisions_Defer
1856 (Generic_Formal_Declarations (N), 'X');
1857 Process_Decisions_Defer
1858 (Parameter_Specifications (Specification (N)), 'X');
1860 -- Task or subprogram body
1862 when N_Subprogram_Body
1863 | N_Task_Body
1865 Set_Statement_Entry;
1866 Traverse_Subprogram_Or_Task_Body (N);
1868 -- Entry body
1870 when N_Entry_Body =>
1871 declare
1872 Cond : constant Node_Id :=
1873 Condition (Entry_Body_Formal_Part (N));
1875 Inner_Dominant : Dominant_Info := No_Dominant;
1877 begin
1878 Set_Statement_Entry;
1880 if Present (Cond) then
1881 Process_Decisions_Defer (Cond, 'G');
1883 -- For an entry body with a barrier, the entry body
1884 -- is dominated by a True evaluation of the barrier.
1886 Inner_Dominant := ('T', N);
1887 end if;
1889 Traverse_Subprogram_Or_Task_Body (N, Inner_Dominant);
1890 end;
1892 -- Protected body
1894 when N_Protected_Body =>
1895 Set_Statement_Entry;
1896 Traverse_Declarations_Or_Statements (Declarations (N));
1898 -- Exit statement, which is an exit statement in the SCO sense,
1899 -- so it is included in the current statement sequence, but
1900 -- then it terminates this sequence. We also have to process
1901 -- any decisions in the exit statement expression.
1903 when N_Exit_Statement =>
1904 Extend_Statement_Sequence (N, 'E');
1905 Process_Decisions_Defer (Condition (N), 'E');
1906 Set_Statement_Entry;
1908 -- If condition is present, then following statement is
1909 -- only executed if the condition evaluates to False.
1911 if Present (Condition (N)) then
1912 Current_Dominant := ('F', N);
1913 else
1914 Current_Dominant := No_Dominant;
1915 end if;
1917 -- Label, which breaks the current statement sequence, but the
1918 -- label itself is not included in the next statement sequence,
1919 -- since it generates no code.
1921 when N_Label =>
1922 Set_Statement_Entry;
1923 Current_Dominant := No_Dominant;
1925 -- Block statement, which breaks the current statement sequence
1927 when N_Block_Statement =>
1928 Set_Statement_Entry;
1930 -- The first statement in the handled sequence of statements
1931 -- is dominated by the elaboration of the last declaration.
1933 Current_Dominant := Traverse_Declarations_Or_Statements
1934 (L => Declarations (N),
1935 D => Current_Dominant);
1937 Traverse_Handled_Statement_Sequence
1938 (N => Handled_Statement_Sequence (N),
1939 D => Current_Dominant);
1941 -- If statement, which breaks the current statement sequence,
1942 -- but we include the condition in the current sequence.
1944 when N_If_Statement =>
1945 Current_Test := N;
1946 Extend_Statement_Sequence (N, 'I');
1947 Process_Decisions_Defer (Condition (N), 'I');
1948 Set_Statement_Entry;
1950 -- Now we traverse the statements in the THEN part
1952 Traverse_Declarations_Or_Statements
1953 (L => Then_Statements (N),
1954 D => ('T', N));
1956 -- Loop through ELSIF parts if present
1958 if Present (Elsif_Parts (N)) then
1959 declare
1960 Saved_Dominant : constant Dominant_Info :=
1961 Current_Dominant;
1963 Elif : Node_Id := First (Elsif_Parts (N));
1965 begin
1966 while Present (Elif) loop
1968 -- An Elsif is executed only if the previous test
1969 -- got a FALSE outcome.
1971 Current_Dominant := ('F', Current_Test);
1973 -- Now update current test information
1975 Current_Test := Elif;
1977 -- We generate a statement sequence for the
1978 -- construct "ELSIF condition", so that we have
1979 -- a statement for the resulting decisions.
1981 Extend_Statement_Sequence (Elif, 'I');
1982 Process_Decisions_Defer (Condition (Elif), 'I');
1983 Set_Statement_Entry;
1985 -- An ELSIF part is never guaranteed to have
1986 -- been executed, following statements are only
1987 -- dominated by the initial IF statement.
1989 Current_Dominant := Saved_Dominant;
1991 -- Traverse the statements in the ELSIF
1993 Traverse_Declarations_Or_Statements
1994 (L => Then_Statements (Elif),
1995 D => ('T', Elif));
1996 Next (Elif);
1997 end loop;
1998 end;
1999 end if;
2001 -- Finally traverse the ELSE statements if present
2003 Traverse_Declarations_Or_Statements
2004 (L => Else_Statements (N),
2005 D => ('F', Current_Test));
2007 -- CASE statement, which breaks the current statement sequence,
2008 -- but we include the expression in the current sequence.
2010 when N_Case_Statement =>
2011 Extend_Statement_Sequence (N, 'C');
2012 Process_Decisions_Defer (Expression (N), 'X');
2013 Set_Statement_Entry;
2015 -- Process case branches, all of which are dominated by the
2016 -- CASE statement.
2018 declare
2019 Alt : Node_Id;
2020 begin
2021 Alt := First_Non_Pragma (Alternatives (N));
2022 while Present (Alt) loop
2023 Traverse_Declarations_Or_Statements
2024 (L => Statements (Alt),
2025 D => Current_Dominant);
2026 Next (Alt);
2027 end loop;
2028 end;
2030 -- ACCEPT statement
2032 when N_Accept_Statement =>
2033 Extend_Statement_Sequence (N, 'A');
2034 Set_Statement_Entry;
2036 -- Process sequence of statements, dominant is the ACCEPT
2037 -- statement.
2039 Traverse_Handled_Statement_Sequence
2040 (N => Handled_Statement_Sequence (N),
2041 D => Current_Dominant);
2043 -- SELECT
2045 when N_Selective_Accept =>
2046 Extend_Statement_Sequence (N, 'S');
2047 Set_Statement_Entry;
2049 -- Process alternatives
2051 declare
2052 Alt : Node_Id;
2053 Guard : Node_Id;
2054 S_Dom : Dominant_Info;
2056 begin
2057 Alt := First (Select_Alternatives (N));
2058 while Present (Alt) loop
2059 S_Dom := Current_Dominant;
2060 Guard := Condition (Alt);
2062 if Present (Guard) then
2063 Process_Decisions
2064 (Guard,
2065 'G',
2066 Pragma_Sloc => No_Location);
2067 Current_Dominant := ('T', Guard);
2068 end if;
2070 Traverse_One (Alt);
2072 Current_Dominant := S_Dom;
2073 Next (Alt);
2074 end loop;
2075 end;
2077 Traverse_Declarations_Or_Statements
2078 (L => Else_Statements (N),
2079 D => Current_Dominant);
2081 when N_Conditional_Entry_Call
2082 | N_Timed_Entry_Call
2084 Extend_Statement_Sequence (N, 'S');
2085 Set_Statement_Entry;
2087 -- Process alternatives
2089 Traverse_One (Entry_Call_Alternative (N));
2091 if Nkind (N) = N_Timed_Entry_Call then
2092 Traverse_One (Delay_Alternative (N));
2093 else
2094 Traverse_Declarations_Or_Statements
2095 (L => Else_Statements (N),
2096 D => Current_Dominant);
2097 end if;
2099 when N_Asynchronous_Select =>
2100 Extend_Statement_Sequence (N, 'S');
2101 Set_Statement_Entry;
2103 Traverse_One (Triggering_Alternative (N));
2104 Traverse_Declarations_Or_Statements
2105 (L => Statements (Abortable_Part (N)),
2106 D => Current_Dominant);
2108 when N_Accept_Alternative =>
2109 Traverse_Declarations_Or_Statements
2110 (L => Statements (N),
2111 D => Current_Dominant,
2112 P => Accept_Statement (N));
2114 when N_Entry_Call_Alternative =>
2115 Traverse_Declarations_Or_Statements
2116 (L => Statements (N),
2117 D => Current_Dominant,
2118 P => Entry_Call_Statement (N));
2120 when N_Delay_Alternative =>
2121 Traverse_Declarations_Or_Statements
2122 (L => Statements (N),
2123 D => Current_Dominant,
2124 P => Delay_Statement (N));
2126 when N_Triggering_Alternative =>
2127 Traverse_Declarations_Or_Statements
2128 (L => Statements (N),
2129 D => Current_Dominant,
2130 P => Triggering_Statement (N));
2132 when N_Terminate_Alternative =>
2134 -- It is dubious to emit a statement SCO for a TERMINATE
2135 -- alternative, since no code is actually executed if the
2136 -- alternative is selected -- the tasking runtime call just
2137 -- never returns???
2139 Extend_Statement_Sequence (N, ' ');
2140 Set_Statement_Entry;
2142 -- Unconditional exit points, which are included in the current
2143 -- statement sequence, but then terminate it
2145 when N_Goto_Statement
2146 | N_Raise_Statement
2147 | N_Requeue_Statement
2149 Extend_Statement_Sequence (N, ' ');
2150 Set_Statement_Entry;
2151 Current_Dominant := No_Dominant;
2153 -- Simple return statement. which is an exit point, but we
2154 -- have to process the return expression for decisions.
2156 when N_Simple_Return_Statement =>
2157 Extend_Statement_Sequence (N, ' ');
2158 Process_Decisions_Defer (Expression (N), 'X');
2159 Set_Statement_Entry;
2160 Current_Dominant := No_Dominant;
2162 -- Extended return statement
2164 when N_Extended_Return_Statement =>
2165 Extend_Statement_Sequence (N, 'R');
2166 Process_Decisions_Defer (Return_Object_Declarations (N), 'X');
2167 Set_Statement_Entry;
2169 Traverse_Handled_Statement_Sequence
2170 (N => Handled_Statement_Sequence (N),
2171 D => Current_Dominant);
2173 Current_Dominant := No_Dominant;
2175 -- Loop ends the current statement sequence, but we include
2176 -- the iteration scheme if present in the current sequence.
2177 -- But the body of the loop starts a new sequence, since it
2178 -- may not be executed as part of the current sequence.
2180 when N_Loop_Statement =>
2181 declare
2182 ISC : constant Node_Id := Iteration_Scheme (N);
2183 Inner_Dominant : Dominant_Info := No_Dominant;
2185 begin
2186 if Present (ISC) then
2188 -- If iteration scheme present, extend the current
2189 -- statement sequence to include the iteration scheme
2190 -- and process any decisions it contains.
2192 -- While loop
2194 if Present (Condition (ISC)) then
2195 Extend_Statement_Sequence (N, 'W');
2196 Process_Decisions_Defer (Condition (ISC), 'W');
2198 -- Set more specific dominant for inner statements
2199 -- (the control sloc for the decision is that of
2200 -- the WHILE token).
2202 Inner_Dominant := ('T', ISC);
2204 -- For loop
2206 else
2207 Extend_Statement_Sequence (N, 'F');
2208 Process_Decisions_Defer
2209 (Loop_Parameter_Specification (ISC), 'X');
2210 end if;
2211 end if;
2213 Set_Statement_Entry;
2215 if Inner_Dominant = No_Dominant then
2216 Inner_Dominant := Current_Dominant;
2217 end if;
2219 Traverse_Declarations_Or_Statements
2220 (L => Statements (N),
2221 D => Inner_Dominant);
2222 end;
2224 -- Pragma
2226 when N_Pragma =>
2228 -- Record sloc of pragma (pragmas don't nest)
2230 pragma Assert (Current_Pragma_Sloc = No_Location);
2231 Current_Pragma_Sloc := Sloc (N);
2233 -- Processing depends on the kind of pragma
2235 declare
2236 Nam : constant Name_Id := Pragma_Name_Unmapped (N);
2237 Arg : Node_Id :=
2238 First (Pragma_Argument_Associations (N));
2239 Typ : Character;
2241 begin
2242 case Nam is
2243 when Name_Assert
2244 | Name_Assert_And_Cut
2245 | Name_Assume
2246 | Name_Check
2247 | Name_Loop_Invariant
2248 | Name_Postcondition
2249 | Name_Precondition
2250 | Name_Type_Invariant
2251 | Name_Invariant
2253 -- For Assert/Check/Precondition/Postcondition, we
2254 -- must generate a P entry for the decision. Note
2255 -- that this is done unconditionally at this stage.
2256 -- Output for disabled pragmas is suppressed later
2257 -- on when we output the decision line in Put_SCOs,
2258 -- depending on setting by Set_SCO_Pragma_Enabled.
2260 if Nam = Name_Check
2261 or else Nam = Name_Type_Invariant
2262 or else Nam = Name_Invariant
2263 then
2264 Next (Arg);
2265 end if;
2267 Process_Decisions_Defer (Expression (Arg), 'P');
2268 Typ := 'p';
2270 -- Pre/postconditions can be inherited so SCO should
2271 -- never be deactivated???
2273 when Name_Debug =>
2274 if Present (Arg) and then Present (Next (Arg)) then
2276 -- Case of a dyadic pragma Debug: first argument
2277 -- is a P decision, any nested decision in the
2278 -- second argument is an X decision.
2280 Process_Decisions_Defer (Expression (Arg), 'P');
2281 Next (Arg);
2282 end if;
2284 Process_Decisions_Defer (Expression (Arg), 'X');
2285 Typ := 'p';
2287 -- For all other pragmas, we generate decision entries
2288 -- for any embedded expressions, and the pragma is
2289 -- never disabled.
2291 -- Should generate P decisions (not X) for assertion
2292 -- related pragmas: [{Static,Dynamic}_]Predicate???
2294 when others =>
2295 Process_Decisions_Defer (N, 'X');
2296 Typ := 'P';
2297 end case;
2299 -- Add statement SCO
2301 Extend_Statement_Sequence (N, Typ);
2303 Current_Pragma_Sloc := No_Location;
2304 end;
2306 -- Object declaration. Ignored if Prev_Ids is set, since the
2307 -- parser generates multiple instances of the whole declaration
2308 -- if there is more than one identifier declared, and we only
2309 -- want one entry in the SCOs, so we take the first, for which
2310 -- Prev_Ids is False.
2312 when N_Number_Declaration
2313 | N_Object_Declaration
2315 if not Prev_Ids (N) then
2316 Extend_Statement_Sequence (N, 'o');
2318 if Has_Decision (N) then
2319 Process_Decisions_Defer (N, 'X');
2320 end if;
2321 end if;
2323 -- All other cases, which extend the current statement sequence
2324 -- but do not terminate it, even if they have nested decisions.
2326 when N_Protected_Type_Declaration
2327 | N_Task_Type_Declaration
2329 Extend_Statement_Sequence (N, 't');
2330 Process_Decisions_Defer (Discriminant_Specifications (N), 'X');
2331 Set_Statement_Entry;
2333 Traverse_Protected_Or_Task_Definition (N);
2335 when N_Single_Protected_Declaration
2336 | N_Single_Task_Declaration
2338 Extend_Statement_Sequence (N, 'o');
2339 Set_Statement_Entry;
2341 Traverse_Protected_Or_Task_Definition (N);
2343 when others =>
2345 -- Determine required type character code, or ASCII.NUL if
2346 -- no SCO should be generated for this node.
2348 declare
2349 NK : constant Node_Kind := Nkind (N);
2350 Typ : Character;
2352 begin
2353 case NK is
2354 when N_Full_Type_Declaration
2355 | N_Incomplete_Type_Declaration
2356 | N_Private_Extension_Declaration
2357 | N_Private_Type_Declaration
2359 Typ := 't';
2361 when N_Subtype_Declaration =>
2362 Typ := 's';
2364 when N_Renaming_Declaration =>
2365 Typ := 'r';
2367 when N_Generic_Instantiation =>
2368 Typ := 'i';
2370 when N_Package_Body_Stub
2371 | N_Protected_Body_Stub
2372 | N_Representation_Clause
2373 | N_Task_Body_Stub
2374 | N_Use_Package_Clause
2375 | N_Use_Type_Clause
2377 Typ := ASCII.NUL;
2379 when N_Procedure_Call_Statement =>
2380 Typ := ' ';
2382 when others =>
2383 if NK in N_Statement_Other_Than_Procedure_Call then
2384 Typ := ' ';
2385 else
2386 Typ := 'd';
2387 end if;
2388 end case;
2390 if Typ /= ASCII.NUL then
2391 Extend_Statement_Sequence (N, Typ);
2392 end if;
2393 end;
2395 -- Process any embedded decisions
2397 if Has_Decision (N) then
2398 Process_Decisions_Defer (N, 'X');
2399 end if;
2400 end case;
2402 -- Process aspects if present
2404 Traverse_Aspects (N);
2405 end Traverse_One;
2407 -- Start of processing for Traverse_Declarations_Or_Statements
2409 begin
2410 -- Process single prefixed node
2412 if Present (P) then
2413 Traverse_One (P);
2414 end if;
2416 -- Loop through statements or declarations
2418 N := First (L);
2419 while Present (N) loop
2421 -- Note: For separate bodies, we see the tree after Par.Labl has
2422 -- introduced implicit labels, so we need to ignore those nodes.
2424 if Nkind (N) /= N_Implicit_Label_Declaration then
2425 Traverse_One (N);
2426 end if;
2428 Next (N);
2429 end loop;
2431 -- End sequence of statements and flush deferred decisions
2433 if Present (P) or else Is_Non_Empty_List (L) then
2434 Set_Statement_Entry;
2435 end if;
2437 return Current_Dominant;
2438 end Traverse_Declarations_Or_Statements;
2440 ------------------------------------------
2441 -- Traverse_Generic_Package_Declaration --
2442 ------------------------------------------
2444 procedure Traverse_Generic_Package_Declaration (N : Node_Id) is
2445 begin
2446 Process_Decisions (Generic_Formal_Declarations (N), 'X', No_Location);
2447 Traverse_Package_Declaration (N);
2448 end Traverse_Generic_Package_Declaration;
2450 -----------------------------------------
2451 -- Traverse_Handled_Statement_Sequence --
2452 -----------------------------------------
2454 procedure Traverse_Handled_Statement_Sequence
2455 (N : Node_Id;
2456 D : Dominant_Info := No_Dominant)
2458 Handler : Node_Id;
2460 begin
2461 -- For package bodies without a statement part, the parser adds an empty
2462 -- one, to normalize the representation. The null statement therein,
2463 -- which does not come from source, does not get a SCO.
2465 if Present (N) and then Comes_From_Source (N) then
2466 Traverse_Declarations_Or_Statements (Statements (N), D);
2468 if Present (Exception_Handlers (N)) then
2469 Handler := First_Non_Pragma (Exception_Handlers (N));
2470 while Present (Handler) loop
2471 Traverse_Declarations_Or_Statements
2472 (L => Statements (Handler),
2473 D => ('E', Handler));
2474 Next (Handler);
2475 end loop;
2476 end if;
2477 end if;
2478 end Traverse_Handled_Statement_Sequence;
2480 ---------------------------
2481 -- Traverse_Package_Body --
2482 ---------------------------
2484 procedure Traverse_Package_Body (N : Node_Id) is
2485 Dom : Dominant_Info;
2486 begin
2487 -- The first statement in the handled sequence of statements is
2488 -- dominated by the elaboration of the last declaration.
2490 Dom := Traverse_Declarations_Or_Statements (Declarations (N));
2492 Traverse_Handled_Statement_Sequence
2493 (Handled_Statement_Sequence (N), Dom);
2494 end Traverse_Package_Body;
2496 ----------------------------------
2497 -- Traverse_Package_Declaration --
2498 ----------------------------------
2500 procedure Traverse_Package_Declaration
2501 (N : Node_Id;
2502 D : Dominant_Info := No_Dominant)
2504 Spec : constant Node_Id := Specification (N);
2505 Dom : Dominant_Info;
2507 begin
2508 Dom :=
2509 Traverse_Declarations_Or_Statements (Visible_Declarations (Spec), D);
2511 -- First private declaration is dominated by last visible declaration
2513 Traverse_Declarations_Or_Statements (Private_Declarations (Spec), Dom);
2514 end Traverse_Package_Declaration;
2516 -------------------------------------------
2517 -- Traverse_Protected_Or_Task_Definition --
2518 -------------------------------------------
2520 procedure Traverse_Protected_Or_Task_Definition (N : Node_Id) is
2521 Dom_Info : Dominant_Info := ('S', N);
2522 -- The first declaration is dominated by the protected or task [type]
2523 -- declaration.
2525 Sync_Def : Node_Id;
2526 -- N's protected or task definition
2528 Priv_Decl : List_Id;
2529 Vis_Decl : List_Id;
2530 -- Sync_Def's Visible_Declarations and Private_Declarations
2532 begin
2533 case Nkind (N) is
2534 when N_Protected_Type_Declaration
2535 | N_Single_Protected_Declaration
2537 Sync_Def := Protected_Definition (N);
2539 when N_Single_Task_Declaration
2540 | N_Task_Type_Declaration
2542 Sync_Def := Task_Definition (N);
2544 when others =>
2545 raise Program_Error;
2546 end case;
2548 -- Sync_Def may be Empty at least for empty Task_Type_Declarations.
2549 -- Querying Visible or Private_Declarations is invalid in this case.
2551 if Present (Sync_Def) then
2552 Vis_Decl := Visible_Declarations (Sync_Def);
2553 Priv_Decl := Private_Declarations (Sync_Def);
2554 else
2555 Vis_Decl := No_List;
2556 Priv_Decl := No_List;
2557 end if;
2559 Dom_Info := Traverse_Declarations_Or_Statements
2560 (L => Vis_Decl,
2561 D => Dom_Info);
2563 -- If visible declarations are present, the first private declaration
2564 -- is dominated by the last visible declaration.
2566 Traverse_Declarations_Or_Statements
2567 (L => Priv_Decl,
2568 D => Dom_Info);
2569 end Traverse_Protected_Or_Task_Definition;
2571 --------------------------------------
2572 -- Traverse_Subprogram_Or_Task_Body --
2573 --------------------------------------
2575 procedure Traverse_Subprogram_Or_Task_Body
2576 (N : Node_Id;
2577 D : Dominant_Info := No_Dominant)
2579 Decls : constant List_Id := Declarations (N);
2580 Dom_Info : Dominant_Info := D;
2582 begin
2583 -- If declarations are present, the first statement is dominated by the
2584 -- last declaration.
2586 Dom_Info := Traverse_Declarations_Or_Statements
2587 (L => Decls, D => Dom_Info);
2589 Traverse_Handled_Statement_Sequence
2590 (N => Handled_Statement_Sequence (N),
2591 D => Dom_Info);
2592 end Traverse_Subprogram_Or_Task_Body;
2594 -------------------------
2595 -- SCO_Record_Filtered --
2596 -------------------------
2598 procedure SCO_Record_Filtered is
2599 type Decision is record
2600 Kind : Character;
2601 -- Type of the SCO decision (see comments for SCO_Table_Entry.C1)
2603 Sloc : Source_Location;
2605 Top : Nat;
2606 -- Index in the SCO_Raw_Table for the root operator/condition for the
2607 -- expression that controls the decision.
2608 end record;
2609 -- Decision descriptor: used to gather information about a candidate
2610 -- SCO decision.
2612 package Pending_Decisions is new Table.Table
2613 (Table_Component_Type => Decision,
2614 Table_Index_Type => Nat,
2615 Table_Low_Bound => 1,
2616 Table_Initial => 1000,
2617 Table_Increment => 200,
2618 Table_Name => "Filter_Pending_Decisions");
2619 -- Table used to hold decisions to process during the collection pass
2621 procedure Add_Expression_Tree (Idx : in out Nat);
2622 -- Add SCO raw table entries for the decision controlling expression
2623 -- tree starting at Idx to the filtered SCO table.
2625 procedure Collect_Decisions
2626 (D : Decision;
2627 Next : out Nat);
2628 -- Collect decisions to add to the filtered SCO table starting at the
2629 -- D decision (including it and its nested operators/conditions). Set
2630 -- Next to the first node index passed the whole decision.
2632 procedure Compute_Range
2633 (Idx : in out Nat;
2634 From : out Source_Location;
2635 To : out Source_Location);
2636 -- Compute the source location range for the expression tree starting at
2637 -- Idx in the SCO raw table. Store its bounds in From and To.
2639 function Is_Decision (Idx : Nat) return Boolean;
2640 -- Return if the expression tree starting at Idx has adjacent nested
2641 -- nodes that make a decision.
2643 procedure Process_Pending_Decisions
2644 (Original_Decision : SCO_Table_Entry);
2645 -- Complete the filtered SCO table using collected decisions. Output
2646 -- decisions inherit the pragma information from the original decision.
2648 procedure Search_Nested_Decisions (Idx : in out Nat);
2649 -- Collect decisions to add to the filtered SCO table starting at the
2650 -- node at Idx in the SCO raw table. This node must not be part of an
2651 -- already-processed decision. Set Idx to the first node index passed
2652 -- the whole expression tree.
2654 procedure Skip_Decision
2655 (Idx : in out Nat;
2656 Process_Nested_Decisions : Boolean);
2657 -- Skip all the nodes that belong to the decision starting at Idx. If
2658 -- Process_Nested_Decision, call Search_Nested_Decisions on the first
2659 -- nested nodes that do not belong to the decision. Set Idx to the first
2660 -- node index passed the whole expression tree.
2662 -------------------------
2663 -- Add_Expression_Tree --
2664 -------------------------
2666 procedure Add_Expression_Tree (Idx : in out Nat) is
2667 Node_Idx : constant Nat := Idx;
2668 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Node_Idx);
2669 From : Source_Location;
2670 To : Source_Location;
2672 begin
2673 case T.C1 is
2674 when ' ' =>
2676 -- This is a single condition. Add an entry for it and move on
2678 SCO_Table.Append (T);
2679 Idx := Idx + 1;
2681 when '!' =>
2683 -- This is a NOT operator: add an entry for it and browse its
2684 -- only child.
2686 SCO_Table.Append (T);
2687 Idx := Idx + 1;
2688 Add_Expression_Tree (Idx);
2690 when others =>
2692 -- This must be an AND/OR/AND THEN/OR ELSE operator
2694 if T.C2 = '?' then
2696 -- This is not a short circuit operator: consider this one
2697 -- and all its children as a single condition.
2699 Compute_Range (Idx, From, To);
2700 SCO_Table.Append
2701 ((From => From,
2702 To => To,
2703 C1 => ' ',
2704 C2 => 'c',
2705 Last => False,
2706 Pragma_Sloc => No_Location,
2707 Pragma_Aspect_Name => No_Name));
2709 else
2710 -- This is a real short circuit operator: add an entry for
2711 -- it and browse its children.
2713 SCO_Table.Append (T);
2714 Idx := Idx + 1;
2715 Add_Expression_Tree (Idx);
2716 Add_Expression_Tree (Idx);
2717 end if;
2718 end case;
2719 end Add_Expression_Tree;
2721 -----------------------
2722 -- Collect_Decisions --
2723 -----------------------
2725 procedure Collect_Decisions
2726 (D : Decision;
2727 Next : out Nat)
2729 Idx : Nat := D.Top;
2731 begin
2732 if D.Kind /= 'X' or else Is_Decision (D.Top) then
2733 Pending_Decisions.Append (D);
2734 end if;
2736 Skip_Decision (Idx, True);
2737 Next := Idx;
2738 end Collect_Decisions;
2740 -------------------
2741 -- Compute_Range --
2742 -------------------
2744 procedure Compute_Range
2745 (Idx : in out Nat;
2746 From : out Source_Location;
2747 To : out Source_Location)
2749 Sloc_F : Source_Location := No_Source_Location;
2750 Sloc_T : Source_Location := No_Source_Location;
2752 procedure Process_One;
2753 -- Process one node of the tree, and recurse over children. Update
2754 -- Idx during the traversal.
2756 -----------------
2757 -- Process_One --
2758 -----------------
2760 procedure Process_One is
2761 begin
2762 if Sloc_F = No_Source_Location
2763 or else
2764 SCO_Raw_Table.Table (Idx).From < Sloc_F
2765 then
2766 Sloc_F := SCO_Raw_Table.Table (Idx).From;
2767 end if;
2769 if Sloc_T = No_Source_Location
2770 or else
2771 Sloc_T < SCO_Raw_Table.Table (Idx).To
2772 then
2773 Sloc_T := SCO_Raw_Table.Table (Idx).To;
2774 end if;
2776 if SCO_Raw_Table.Table (Idx).C1 = ' ' then
2778 -- This is a condition: nothing special to do
2780 Idx := Idx + 1;
2782 elsif SCO_Raw_Table.Table (Idx).C1 = '!' then
2784 -- The "not" operator has only one operand
2786 Idx := Idx + 1;
2787 Process_One;
2789 else
2790 -- This is an AND THEN or OR ELSE logical operator: follow the
2791 -- left, then the right operands.
2793 Idx := Idx + 1;
2795 Process_One;
2796 Process_One;
2797 end if;
2798 end Process_One;
2800 -- Start of processing for Compute_Range
2802 begin
2803 Process_One;
2804 From := Sloc_F;
2805 To := Sloc_T;
2806 end Compute_Range;
2808 -----------------
2809 -- Is_Decision --
2810 -----------------
2812 function Is_Decision (Idx : Nat) return Boolean is
2813 Index : Nat := Idx;
2815 begin
2816 loop
2817 declare
2818 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
2820 begin
2821 case T.C1 is
2822 when ' ' =>
2823 return False;
2825 when '!' =>
2827 -- This is a decision iff the only operand of the NOT
2828 -- operator could be a standalone decision.
2830 Index := Idx + 1;
2832 when others =>
2834 -- This node is a logical operator (and thus could be a
2835 -- standalone decision) iff it is a short circuit
2836 -- operator.
2838 return T.C2 /= '?';
2839 end case;
2840 end;
2841 end loop;
2842 end Is_Decision;
2844 -------------------------------
2845 -- Process_Pending_Decisions --
2846 -------------------------------
2848 procedure Process_Pending_Decisions
2849 (Original_Decision : SCO_Table_Entry)
2851 begin
2852 for Index in 1 .. Pending_Decisions.Last loop
2853 declare
2854 D : Decision renames Pending_Decisions.Table (Index);
2855 Idx : Nat := D.Top;
2857 begin
2858 -- Add a SCO table entry for the decision itself
2860 pragma Assert (D.Kind /= ' ');
2862 SCO_Table.Append
2863 ((To => No_Source_Location,
2864 From => D.Sloc,
2865 C1 => D.Kind,
2866 C2 => ' ',
2867 Last => False,
2868 Pragma_Sloc => Original_Decision.Pragma_Sloc,
2869 Pragma_Aspect_Name =>
2870 Original_Decision.Pragma_Aspect_Name));
2872 -- Then add ones for its nested operators/operands. Do not
2873 -- forget to tag its *last* entry as such.
2875 Add_Expression_Tree (Idx);
2876 SCO_Table.Table (SCO_Table.Last).Last := True;
2877 end;
2878 end loop;
2880 -- Clear the pending decisions list
2881 Pending_Decisions.Set_Last (0);
2882 end Process_Pending_Decisions;
2884 -----------------------------
2885 -- Search_Nested_Decisions --
2886 -----------------------------
2888 procedure Search_Nested_Decisions (Idx : in out Nat) is
2889 begin
2890 loop
2891 declare
2892 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2894 begin
2895 case T.C1 is
2896 when ' ' =>
2897 Idx := Idx + 1;
2898 exit;
2900 when '!' =>
2901 Collect_Decisions
2902 ((Kind => 'X',
2903 Sloc => T.From,
2904 Top => Idx),
2905 Idx);
2906 exit;
2908 when others =>
2909 if T.C2 = '?' then
2911 -- This is not a logical operator: start looking for
2912 -- nested decisions from here. Recurse over the left
2913 -- child and let the loop take care of the right one.
2915 Idx := Idx + 1;
2916 Search_Nested_Decisions (Idx);
2918 else
2919 -- We found a nested decision
2921 Collect_Decisions
2922 ((Kind => 'X',
2923 Sloc => T.From,
2924 Top => Idx),
2925 Idx);
2926 exit;
2927 end if;
2928 end case;
2929 end;
2930 end loop;
2931 end Search_Nested_Decisions;
2933 -------------------
2934 -- Skip_Decision --
2935 -------------------
2937 procedure Skip_Decision
2938 (Idx : in out Nat;
2939 Process_Nested_Decisions : Boolean)
2941 begin
2942 loop
2943 declare
2944 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2946 begin
2947 Idx := Idx + 1;
2949 case T.C1 is
2950 when ' ' =>
2951 exit;
2953 when '!' =>
2955 -- This NOT operator belongs to the outside decision:
2956 -- just skip it.
2958 null;
2960 when others =>
2961 if T.C2 = '?' and then Process_Nested_Decisions then
2963 -- This is not a logical operator: start looking for
2964 -- nested decisions from here. Recurse over the left
2965 -- child and let the loop take care of the right one.
2967 Search_Nested_Decisions (Idx);
2969 else
2970 -- This is a logical operator, so it belongs to the
2971 -- outside decision: skip its left child, then let the
2972 -- loop take care of the right one.
2974 Skip_Decision (Idx, Process_Nested_Decisions);
2975 end if;
2976 end case;
2977 end;
2978 end loop;
2979 end Skip_Decision;
2981 -- Start of processing for SCO_Record_Filtered
2983 begin
2984 -- Filtering must happen only once: do nothing if it this pass was
2985 -- already run.
2987 if SCO_Generation_State = Filtered then
2988 return;
2989 else
2990 pragma Assert (SCO_Generation_State = Raw);
2991 SCO_Generation_State := Filtered;
2992 end if;
2994 -- Loop through all SCO entries under SCO units
2996 for Unit_Idx in 1 .. SCO_Unit_Table.Last loop
2997 declare
2998 Unit : SCO_Unit_Table_Entry
2999 renames SCO_Unit_Table.Table (Unit_Idx);
3001 Idx : Nat := Unit.From;
3002 -- Index of the current SCO raw table entry
3004 New_From : constant Nat := SCO_Table.Last + 1;
3005 -- After copying SCO enties of interest to the final table, we
3006 -- will have to change the From/To indexes this unit targets.
3007 -- This constant keeps track of the new From index.
3009 begin
3010 while Idx <= Unit.To loop
3011 declare
3012 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
3014 begin
3015 case T.C1 is
3017 -- Decision (of any kind, including pragmas and aspects)
3019 when 'E' | 'G' | 'I' | 'W' | 'X' | 'P' | 'a' | 'A' =>
3020 if SCO_Pragma_Disabled (T.Pragma_Sloc) then
3022 -- Skip SCO entries for decisions in disabled
3023 -- constructs (pragmas or aspects).
3025 Idx := Idx + 1;
3026 Skip_Decision (Idx, False);
3028 else
3029 Collect_Decisions
3030 ((Kind => T.C1,
3031 Sloc => T.From,
3032 Top => Idx + 1),
3033 Idx);
3034 Process_Pending_Decisions (T);
3035 end if;
3037 -- There is no translation/filtering to do for other kind
3038 -- of SCO items (statements, dominance markers, etc.).
3040 when '|' | '&' | '!' | ' ' =>
3042 -- SCO logical operators and conditions cannot exist
3043 -- on their own: they must be inside a decision (such
3044 -- entries must have been skipped by
3045 -- Collect_Decisions).
3047 raise Program_Error;
3049 when others =>
3050 SCO_Table.Append (T);
3051 Idx := Idx + 1;
3052 end case;
3053 end;
3054 end loop;
3056 -- Now, update the SCO entry indexes in the unit entry
3058 Unit.From := New_From;
3059 Unit.To := SCO_Table.Last;
3060 end;
3061 end loop;
3063 -- Then clear the raw table to free bytes
3065 SCO_Raw_Table.Free;
3066 end SCO_Record_Filtered;
3068 end Par_SCO;