1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 2009-2015, Free Software Foundation, Inc. --
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. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Aspects
; use Aspects
;
27 with Atree
; use Atree
;
28 with Debug
; use Debug
;
29 with Errout
; use Errout
;
31 with Lib
.Util
; use Lib
.Util
;
32 with Namet
; use Namet
;
33 with Nlists
; use Nlists
;
35 with Output
; use Output
;
39 with Sem_Util
; use Sem_Util
;
40 with Sinfo
; use Sinfo
;
41 with Sinput
; use Sinput
;
42 with Snames
; use Snames
;
45 with GNAT
.HTable
; use GNAT
.HTable
;
46 with GNAT
.Heap_Sort_G
;
49 package body Par_SCO
is
51 --------------------------
52 -- First-pass SCO table --
53 --------------------------
55 -- The Short_Circuit_And_Or pragma enables one to use AND and OR operators
56 -- in source code while the ones used with booleans will be interpreted as
57 -- their short circuit alternatives (AND THEN and OR ELSE). Thus, the true
58 -- meaning of these operators is known only after the semantic analysis.
60 -- However, decision SCOs include short circuit operators only. The SCO
61 -- information generation pass must be done before expansion, hence before
62 -- the semantic analysis. Because of this, the SCO information generation
63 -- is done in two passes.
65 -- The first one (SCO_Record_Raw, before semantic analysis) completes the
66 -- SCO_Raw_Table assuming all AND/OR operators are short circuit ones.
67 -- Then, the semantic analysis determines which operators are promoted to
68 -- short circuit ones. Finally, the second pass (SCO_Record_Filtered)
69 -- translates the SCO_Raw_Table to SCO_Table, taking care of removing the
70 -- remaining AND/OR operators and of adjusting decisions accordingly
71 -- (splitting decisions, removing empty ones, etc.).
73 type SCO_Generation_State_Type
is (None
, Raw
, Filtered
);
74 SCO_Generation_State
: SCO_Generation_State_Type
:= None
;
75 -- Keep track of the SCO generation state: this will prevent us from
76 -- running some steps multiple times (the second pass has to be started
77 -- from multiple places).
79 package SCO_Raw_Table
is new GNAT
.Table
80 (Table_Component_Type
=> SCO_Table_Entry
,
81 Table_Index_Type
=> Nat
,
84 Table_Increment
=> 300);
86 -----------------------
87 -- Unit Number Table --
88 -----------------------
90 -- This table parallels the SCO_Unit_Table, keeping track of the unit
91 -- numbers corresponding to the entries made in this table, so that before
92 -- writing out the SCO information to the ALI file, we can fill in the
93 -- proper dependency numbers and file names.
95 -- Note that the zero'th entry is here for convenience in sorting the
96 -- table, the real lower bound is 1.
98 package SCO_Unit_Number_Table
is new Table
.Table
99 (Table_Component_Type
=> Unit_Number_Type
,
100 Table_Index_Type
=> SCO_Unit_Index
,
101 Table_Low_Bound
=> 0, -- see note above on sort
103 Table_Increment
=> 200,
104 Table_Name
=> "SCO_Unit_Number_Entry");
106 ------------------------------------------
107 -- Condition/Operator/Pragma Hash Table --
108 ------------------------------------------
110 -- We need to be able to get to conditions quickly for handling the calls
111 -- to Set_SCO_Condition efficiently, and similarly to get to pragmas to
112 -- handle calls to Set_SCO_Pragma_Enabled (the same holds for operators and
113 -- Set_SCO_Logical_Operator). For this purpose we identify the conditions,
114 -- operators and pragmas in the table by their starting sloc, and use this
115 -- hash table to map from these sloc values to SCO_Table indexes.
117 type Header_Num
is new Integer range 0 .. 996;
118 -- Type for hash table headers
120 function Hash
(F
: Source_Ptr
) return Header_Num
;
121 -- Function to Hash source pointer value
123 function Equal
(F1
: Source_Ptr
; F2
: Source_Ptr
) return Boolean;
124 -- Function to test two keys for equality
126 function "<" (S1
: Source_Location
; S2
: Source_Location
) return Boolean;
127 -- Function to test for source locations order
129 package SCO_Raw_Hash_Table
is new Simple_HTable
130 (Header_Num
, Int
, 0, Source_Ptr
, Hash
, Equal
);
131 -- The actual hash table
133 --------------------------
134 -- Internal Subprograms --
135 --------------------------
137 function Has_Decision
(N
: Node_Id
) return Boolean;
138 -- N is the node for a subexpression. Returns True if the subexpression
139 -- contains a nested decision (i.e. either is a logical operator, or
140 -- contains a logical operator in its subtree).
142 -- This must be used in the first pass (SCO_Record_Raw) only: here AND/OR
143 -- operators are considered as short circuit, just in case the
144 -- Short_Circuit_And_Or pragma is used: only real short circuit operations
145 -- will be kept in the secord pass.
147 type Tristate
is (False, True, Unknown
);
149 function Is_Logical_Operator
(N
: Node_Id
) return Tristate
;
150 -- N is the node for a subexpression. This procedure determines whether N
151 -- is a logical operator: True for short circuit conditions, Unknown for OR
152 -- and AND (the Short_Circuit_And_Or pragma may be used) and False
153 -- otherwise. Note that in cases where True is returned, callers assume
154 -- Nkind (N) in N_Op.
156 function To_Source_Location
(S
: Source_Ptr
) return Source_Location
;
157 -- Converts Source_Ptr value to Source_Location (line/col) format
159 procedure Process_Decisions
162 Pragma_Sloc
: Source_Ptr
);
163 -- If N is Empty, has no effect. Otherwise scans the tree for the node N,
164 -- to output any decisions it contains. T is one of IEGPWX (for context of
165 -- expression: if/exit when/entry guard/pragma/while/expression). If T is
166 -- other than X, the node N is the if expression involved, and a decision
167 -- is always present (at the very least a simple decision is present at the
170 procedure Process_Decisions
173 Pragma_Sloc
: Source_Ptr
);
174 -- Calls above procedure for each element of the list L
176 procedure Set_Raw_Table_Entry
182 Pragma_Sloc
: Source_Ptr
:= No_Location
;
183 Pragma_Aspect_Name
: Name_Id
:= No_Name
);
184 -- Append an entry to SCO_Raw_Table with fields set as per arguments
186 type Dominant_Info
is record
188 -- F/T/S/E for a valid dominance marker, or ' ' for no dominant
191 -- Node providing the Sloc(s) for the dominance marker
193 No_Dominant
: constant Dominant_Info
:= (' ', Empty
);
195 procedure Record_Instance
(Id
: Instance_Id
; Inst_Sloc
: Source_Ptr
);
196 -- Add one entry from the instance table to the corresponding SCO table
198 procedure Traverse_Declarations_Or_Statements
200 D
: Dominant_Info
:= No_Dominant
;
201 P
: Node_Id
:= Empty
);
202 -- Process L, a list of statements or declarations dominated by D. If P is
203 -- present, it is processed as though it had been prepended to L.
205 function Traverse_Declarations_Or_Statements
207 D
: Dominant_Info
:= No_Dominant
;
208 P
: Node_Id
:= Empty
) return Dominant_Info
;
209 -- Same as above, and returns dominant information corresponding to the
210 -- last node with SCO in L.
212 -- The following Traverse_* routines perform appropriate calls to
213 -- Traverse_Declarations_Or_Statements to traverse specific node kinds.
214 -- Parameter D, when present, indicates the dominant of the first
215 -- declaration or statement within N.
217 -- Why is Traverse_Sync_Definition commented specificaly and
218 -- the others are not???
220 procedure Traverse_Generic_Package_Declaration
(N
: Node_Id
);
222 procedure Traverse_Handled_Statement_Sequence
224 D
: Dominant_Info
:= No_Dominant
);
226 procedure Traverse_Package_Body
(N
: Node_Id
);
228 procedure Traverse_Package_Declaration
230 D
: Dominant_Info
:= No_Dominant
);
232 procedure Traverse_Subprogram_Or_Task_Body
234 D
: Dominant_Info
:= No_Dominant
);
236 procedure Traverse_Sync_Definition
(N
: Node_Id
);
237 -- Traverse a protected definition or task definition
239 -- Note regarding traversals: In a few cases where an Alternatives list is
240 -- involved, pragmas such as "pragma Page" may show up before the first
241 -- alternative. We skip them because we're out of statement or declaration
242 -- context, so these can't be pragmas of interest for SCO purposes, and
243 -- the regular alternative processing typically involves attribute queries
244 -- which aren't valid for a pragma.
246 procedure Write_SCOs_To_ALI_File
is new Put_SCOs
;
247 -- Write SCO information to the ALI file using routines in Lib.Util
254 procedure Dump_Entry
(Index
: Nat
; T
: SCO_Table_Entry
);
255 -- Dump a SCO table entry
261 procedure Dump_Entry
(Index
: Nat
; T
: SCO_Table_Entry
) is
268 Write_Str
(" C1 = '");
274 Write_Str
(" C2 = '");
279 if T
.From
/= No_Source_Location
then
280 Write_Str
(" From = ");
281 Write_Int
(Int
(T
.From
.Line
));
283 Write_Int
(Int
(T
.From
.Col
));
286 if T
.To
/= No_Source_Location
then
287 Write_Str
(" To = ");
288 Write_Int
(Int
(T
.To
.Line
));
290 Write_Int
(Int
(T
.To
.Col
));
296 Write_Str
(" False");
302 -- Start of processing for dsco
305 -- Dump SCO unit table
307 Write_Line
("SCO Unit Table");
308 Write_Line
("--------------");
310 for Index
in 1 .. SCO_Unit_Table
.Last
loop
312 UTE
: SCO_Unit_Table_Entry
renames SCO_Unit_Table
.Table
(Index
);
316 Write_Int
(Int
(Index
));
317 Write_Str
(" Dep_Num = ");
318 Write_Int
(Int
(UTE
.Dep_Num
));
319 Write_Str
(" From = ");
320 Write_Int
(Int
(UTE
.From
));
321 Write_Str
(" To = ");
322 Write_Int
(Int
(UTE
.To
));
324 Write_Str
(" File_Name = """);
326 if UTE
.File_Name
/= null then
327 Write_Str
(UTE
.File_Name
.all);
335 -- Dump SCO Unit number table if it contains any entries
337 if SCO_Unit_Number_Table
.Last
>= 1 then
339 Write_Line
("SCO Unit Number Table");
340 Write_Line
("---------------------");
342 for Index
in 1 .. SCO_Unit_Number_Table
.Last
loop
344 Write_Int
(Int
(Index
));
345 Write_Str
(". Unit_Number = ");
346 Write_Int
(Int
(SCO_Unit_Number_Table
.Table
(Index
)));
351 -- Dump SCO raw-table
354 Write_Line
("SCO Raw Table");
355 Write_Line
("---------");
357 if SCO_Generation_State
= Filtered
then
358 Write_Line
("Empty (free'd after second pass)");
360 for Index
in 1 .. SCO_Raw_Table
.Last
loop
361 Dump_Entry
(Index
, SCO_Raw_Table
.Table
(Index
));
365 -- Dump SCO table itself
368 Write_Line
("SCO Filtered Table");
369 Write_Line
("---------");
371 for Index
in 1 .. SCO_Table
.Last
loop
372 Dump_Entry
(Index
, SCO_Table
.Table
(Index
));
380 function Equal
(F1
: Source_Ptr
; F2
: Source_Ptr
) return Boolean is
389 function "<" (S1
: Source_Location
; S2
: Source_Location
) return Boolean is
391 return S1
.Line
< S2
.Line
392 or else (S1
.Line
= S2
.Line
and then S1
.Col
< S2
.Col
);
399 function Has_Decision
(N
: Node_Id
) return Boolean is
400 function Check_Node
(N
: Node_Id
) return Traverse_Result
;
401 -- Determine if Nkind (N) indicates the presence of a decision (i.e. N
402 -- is a logical operator, which is a decision in itself, or an
403 -- IF-expression whose Condition attribute is a decision).
409 function Check_Node
(N
: Node_Id
) return Traverse_Result
is
411 -- If we are not sure this is a logical operator (AND and OR may be
412 -- turned into logical operators with the Short_Circuit_And_Or
413 -- pragma), assume it is. Putative decisions will be discarded if
414 -- needed in the secord pass.
416 if Is_Logical_Operator
(N
) /= False
417 or else Nkind
(N
) = N_If_Expression
425 function Traverse
is new Traverse_Func
(Check_Node
);
427 -- Start of processing for Has_Decision
430 return Traverse
(N
) = Abandon
;
437 function Hash
(F
: Source_Ptr
) return Header_Num
is
439 return Header_Num
(Nat
(F
) mod 997);
446 procedure Initialize
is
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
;
456 -------------------------
457 -- Is_Logical_Operator --
458 -------------------------
460 function Is_Logical_Operator
(N
: Node_Id
) return Tristate
is
462 if Nkind_In
(N
, N_And_Then
, N_Op_Not
, N_Or_Else
) then
464 elsif Nkind_In
(N
, N_Op_And
, N_Op_Or
) then
469 end Is_Logical_Operator
;
471 -----------------------
472 -- Process_Decisions --
473 -----------------------
475 -- Version taking a list
477 procedure Process_Decisions
480 Pragma_Sloc
: Source_Ptr
)
487 while Present
(N
) loop
488 Process_Decisions
(N
, T
, Pragma_Sloc
);
492 end Process_Decisions
;
494 -- Version taking a node
496 Current_Pragma_Sloc
: Source_Ptr
:= No_Location
;
497 -- While processing a pragma, this is set to the sloc of the N_Pragma node
499 procedure Process_Decisions
502 Pragma_Sloc
: Source_Ptr
)
505 -- This is used to mark the location of a decision sequence in the SCO
506 -- table. We use it for backing out a simple decision in an expression
507 -- context that contains only NOT operators.
510 -- Likewise for the putative SCO_Raw_Hash_Table entries: see below
512 type Hash_Entry
is record
516 -- We must register all conditions/pragmas in SCO_Raw_Hash_Table.
517 -- However we cannot register them in the same time we are adding the
518 -- corresponding SCO entries to the raw table since we may discard them
519 -- later on. So instead we put all putative conditions into Hash_Entries
520 -- (see below) and register them once we are sure we keep them.
522 -- This data structure holds the conditions/pragmas to register in
523 -- SCO_Raw_Hash_Table.
525 package Hash_Entries
is new Table
.Table
526 (Table_Component_Type
=> Hash_Entry
,
527 Table_Index_Type
=> Nat
,
528 Table_Low_Bound
=> 1,
530 Table_Increment
=> 10,
531 Table_Name
=> "Hash_Entries");
532 -- Hold temporarily (i.e. free'd before returning) the Hash_Entry before
533 -- they are registered in SCO_Raw_Hash_Table.
535 X_Not_Decision
: Boolean;
536 -- This flag keeps track of whether a decision sequence in the SCO table
537 -- contains only NOT operators, and is for an expression context (T=X).
538 -- The flag will be set False if T is other than X, or if an operator
539 -- other than NOT is in the sequence.
541 procedure Output_Decision_Operand
(N
: Node_Id
);
542 -- The node N is the top level logical operator of a decision, or it is
543 -- one of the operands of a logical operator belonging to a single
544 -- complex decision. This routine outputs the sequence of table entries
545 -- corresponding to the node. Note that we do not process the sub-
546 -- operands to look for further decisions, that processing is done in
547 -- Process_Decision_Operand, because we can't get decisions mixed up in
548 -- the global table. Call has no effect if N is Empty.
550 procedure Output_Element
(N
: Node_Id
);
551 -- Node N is an operand of a logical operator that is not itself a
552 -- logical operator, or it is a simple decision. This routine outputs
553 -- the table entry for the element, with C1 set to ' '. Last is set
554 -- False, and an entry is made in the condition hash table.
556 procedure Output_Header
(T
: Character);
557 -- Outputs a decision header node. T is I/W/E/P for IF/WHILE/EXIT WHEN/
558 -- PRAGMA, and 'X' for the expression case.
560 procedure Process_Decision_Operand
(N
: Node_Id
);
561 -- This is called on node N, the top level node of a decision, or on one
562 -- of its operands or suboperands after generating the full output for
563 -- the complex decision. It process the suboperands of the decision
564 -- looking for nested decisions.
566 function Process_Node
(N
: Node_Id
) return Traverse_Result
;
567 -- Processes one node in the traversal, looking for logical operators,
568 -- and if one is found, outputs the appropriate table entries.
570 -----------------------------
571 -- Output_Decision_Operand --
572 -----------------------------
574 procedure Output_Decision_Operand
(N
: Node_Id
) is
577 -- C1 holds a character that identifies the operation while C2
578 -- indicates whether we are sure (' ') or not ('?') this operation
579 -- belongs to the decision. '?' entries will be filtered out in the
580 -- second (SCO_Record_Filtered) pass.
590 T
:= Is_Logical_Operator
(N
);
595 if Nkind
(N
) = N_Op_Not
then
602 if Nkind_In
(N
, N_Op_Or
, N_Or_Else
) then
604 else pragma Assert
(Nkind_In
(N
, N_Op_And
, N_And_Then
));
622 Hash_Entries
.Append
((Sloc
(N
), SCO_Raw_Table
.Last
));
624 Output_Decision_Operand
(L
);
625 Output_Decision_Operand
(Right_Opnd
(N
));
627 -- Not a logical operator
632 end Output_Decision_Operand
;
638 procedure Output_Element
(N
: Node_Id
) is
642 Sloc_Range
(N
, FSloc
, LSloc
);
649 Hash_Entries
.Append
((FSloc
, SCO_Raw_Table
.Last
));
656 procedure Output_Header
(T
: Character) is
657 Loc
: Source_Ptr
:= No_Location
;
658 -- Node whose Sloc is used for the decision
660 Nam
: Name_Id
:= No_Name
;
661 -- For the case of an aspect, aspect name
665 when 'I' |
'E' |
'W' |
'a' |
'A' =>
667 -- For IF, EXIT, WHILE, or aspects, the token SLOC is that of
668 -- the parent of the expression.
670 Loc
:= Sloc
(Parent
(N
));
672 if T
= 'a' or else T
= 'A' then
673 Nam
:= Chars
(Identifier
(Parent
(N
)));
678 -- For entry guard, the token sloc is from the N_Entry_Body.
679 -- For PRAGMA, we must get the location from the pragma node.
680 -- Argument N is the pragma argument, and we have to go up
681 -- two levels (through the pragma argument association) to
682 -- get to the pragma node itself. For the guard on a select
683 -- alternative, we do not have access to the token location for
684 -- the WHEN, so we use the first sloc of the condition itself
685 -- (note: we use First_Sloc, not Sloc, because this is what is
686 -- referenced by dominance markers).
688 -- Doesn't this requirement of using First_Sloc need to be
689 -- documented in the spec ???
691 if Nkind_In
(Parent
(N
), N_Accept_Alternative
,
693 N_Terminate_Alternative
)
695 Loc
:= First_Sloc
(N
);
697 Loc
:= Sloc
(Parent
(Parent
(N
)));
702 -- For an expression, no Sloc
706 -- No other possibilities
718 Pragma_Sloc
=> Pragma_Sloc
,
719 Pragma_Aspect_Name
=> Nam
);
721 -- For an aspect specification, which will be rewritten into a
722 -- pragma, enter a hash table entry now.
725 Hash_Entries
.Append
((Loc
, SCO_Raw_Table
.Last
));
729 ------------------------------
730 -- Process_Decision_Operand --
731 ------------------------------
733 procedure Process_Decision_Operand
(N
: Node_Id
) is
735 if Is_Logical_Operator
(N
) /= False then
736 if Nkind
(N
) /= N_Op_Not
then
737 Process_Decision_Operand
(Left_Opnd
(N
));
738 X_Not_Decision
:= False;
741 Process_Decision_Operand
(Right_Opnd
(N
));
744 Process_Decisions
(N
, 'X', Pragma_Sloc
);
746 end Process_Decision_Operand
;
752 function Process_Node
(N
: Node_Id
) return Traverse_Result
is
756 -- Logical operators, output table entries and then process
757 -- operands recursively to deal with nested conditions.
759 when N_And_Then | N_Or_Else | N_Op_Not | N_Op_And | N_Op_Or
=>
764 -- If outer level, then type comes from call, otherwise it
765 -- is more deeply nested and counts as X for expression.
767 if N
= Process_Decisions
.N
then
768 T
:= Process_Decisions
.T
;
773 -- Output header for sequence
775 X_Not_Decision
:= T
= 'X' and then Nkind
(N
) = N_Op_Not
;
776 Mark
:= SCO_Raw_Table
.Last
;
777 Mark_Hash
:= Hash_Entries
.Last
;
780 -- Output the decision
782 Output_Decision_Operand
(N
);
784 -- If the decision was in an expression context (T = 'X')
785 -- and contained only NOT operators, then we don't output
788 if X_Not_Decision
then
789 SCO_Raw_Table
.Set_Last
(Mark
);
790 Hash_Entries
.Set_Last
(Mark_Hash
);
792 -- Otherwise, set Last in last table entry to mark end
795 SCO_Raw_Table
.Table
(SCO_Raw_Table
.Last
).Last
:= True;
798 -- Process any embedded decisions
800 Process_Decision_Operand
(N
);
806 -- Really hard to believe this is correct given the special
807 -- handling for if expressions below ???
809 when N_Case_Expression
=>
812 -- If expression, processed like an if statement
814 when N_If_Expression
=>
816 Cond
: constant Node_Id
:= First
(Expressions
(N
));
817 Thnx
: constant Node_Id
:= Next
(Cond
);
818 Elsx
: constant Node_Id
:= Next
(Thnx
);
821 Process_Decisions
(Cond
, 'I', Pragma_Sloc
);
822 Process_Decisions
(Thnx
, 'X', Pragma_Sloc
);
823 Process_Decisions
(Elsx
, 'X', Pragma_Sloc
);
827 -- All other cases, continue scan
835 procedure Traverse
is new Traverse_Proc
(Process_Node
);
837 -- Start of processing for Process_Decisions
846 -- See if we have simple decision at outer level and if so then
847 -- generate the decision entry for this simple decision. A simple
848 -- decision is a boolean expression (which is not a logical operator
849 -- or short circuit form) appearing as the operand of an IF, WHILE,
850 -- EXIT WHEN, or special PRAGMA construct.
852 if T
/= 'X' and then Is_Logical_Operator
(N
) = False then
856 -- Change Last in last table entry to True to mark end of
857 -- sequence, which is this case is only one element long.
859 SCO_Raw_Table
.Table
(SCO_Raw_Table
.Last
).Last
:= True;
864 -- Now we have the definitive set of SCO entries, register them in the
865 -- corresponding hash table.
867 for J
in 1 .. Hash_Entries
.Last
loop
868 SCO_Raw_Hash_Table
.Set
869 (Hash_Entries
.Table
(J
).Sloc
,
870 Hash_Entries
.Table
(J
).SCO_Index
);
874 end Process_Decisions
;
881 procedure Write_Info_Char
(C
: Character) renames Write_Char
;
882 -- Write one character;
884 procedure Write_Info_Initiate
(Key
: Character) renames Write_Char
;
885 -- Start new one and write one character;
887 procedure Write_Info_Nat
(N
: Nat
);
890 procedure Write_Info_Terminate
renames Write_Eol
;
891 -- Terminate current line
897 procedure Write_Info_Nat
(N
: Nat
) is
902 procedure Debug_Put_SCOs
is new Put_SCOs
;
904 -- Start of processing for pscos
910 ---------------------
911 -- Record_Instance --
912 ---------------------
914 procedure Record_Instance
(Id
: Instance_Id
; Inst_Sloc
: Source_Ptr
) is
915 Inst_Src
: constant Source_File_Index
:=
916 Get_Source_File_Index
(Inst_Sloc
);
918 SCO_Instance_Table
.Append
919 ((Inst_Dep_Num
=> Dependency_Num
(Unit
(Inst_Src
)),
920 Inst_Loc
=> To_Source_Location
(Inst_Sloc
),
921 Enclosing_Instance
=> SCO_Instance_Index
(Instance
(Inst_Src
))));
924 (SCO_Instance_Table
.Last
= SCO_Instance_Index
(Id
));
931 procedure SCO_Output
is
932 procedure Populate_SCO_Instance_Table
is
933 new Sinput
.Iterate_On_Instances
(Record_Instance
);
936 pragma Assert
(SCO_Generation_State
= Filtered
);
938 if Debug_Flag_Dot_OO
then
942 Populate_SCO_Instance_Table
;
944 -- Sort the unit tables based on dependency numbers
946 Unit_Table_Sort
: declare
947 function Lt
(Op1
: Natural; Op2
: Natural) return Boolean;
948 -- Comparison routine for sort call
950 procedure Move
(From
: Natural; To
: Natural);
951 -- Move routine for sort call
957 function Lt
(Op1
: Natural; Op2
: Natural) return Boolean is
961 (SCO_Unit_Number_Table
.Table
(SCO_Unit_Index
(Op1
)))
964 (SCO_Unit_Number_Table
.Table
(SCO_Unit_Index
(Op2
)));
971 procedure Move
(From
: Natural; To
: Natural) is
973 SCO_Unit_Table
.Table
(SCO_Unit_Index
(To
)) :=
974 SCO_Unit_Table
.Table
(SCO_Unit_Index
(From
));
975 SCO_Unit_Number_Table
.Table
(SCO_Unit_Index
(To
)) :=
976 SCO_Unit_Number_Table
.Table
(SCO_Unit_Index
(From
));
979 package Sorting
is new GNAT
.Heap_Sort_G
(Move
, Lt
);
981 -- Start of processing for Unit_Table_Sort
984 Sorting
.Sort
(Integer (SCO_Unit_Table
.Last
));
987 -- Loop through entries in the unit table to set file name and
988 -- dependency number entries.
990 for J
in 1 .. SCO_Unit_Table
.Last
loop
992 U
: constant Unit_Number_Type
:= SCO_Unit_Number_Table
.Table
(J
);
993 UTE
: SCO_Unit_Table_Entry
renames SCO_Unit_Table
.Table
(J
);
996 Get_Name_String
(Reference_Name
(Source_Index
(U
)));
997 UTE
.File_Name
:= new String'(Name_Buffer (1 .. Name_Len));
998 UTE.Dep_Num := Dependency_Num (U);
1002 -- Now the tables are all setup for output to the ALI file
1004 Write_SCOs_To_ALI_File;
1007 -------------------------
1008 -- SCO_Pragma_Disabled --
1009 -------------------------
1011 function SCO_Pragma_Disabled (Loc : Source_Ptr) return Boolean is
1015 if Loc = No_Location then
1019 Index := SCO_Raw_Hash_Table.Get (Loc);
1021 -- The test here for zero is to deal with possible previous errors, and
1022 -- for the case of pragma statement SCOs, for which we always set the
1023 -- Pragma_Sloc even if the particular pragma cannot be specifically
1028 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1038 -- Aspect decision (enabled)
1043 -- Aspect decision (not enabled)
1048 -- Nullified disabled SCO
1053 raise Program_Error;
1060 end SCO_Pragma_Disabled;
1062 --------------------
1063 -- SCO_Record_Raw --
1064 --------------------
1066 procedure SCO_Record_Raw (U : Unit_Number_Type) is
1067 procedure Traverse_Aux_Decls (N : Node_Id);
1068 -- Traverse the Aux_Decls_Node of compilation unit N
1070 ------------------------
1071 -- Traverse_Aux_Decls --
1072 ------------------------
1074 procedure Traverse_Aux_Decls (N : Node_Id) is
1075 ADN : constant Node_Id := Aux_Decls_Node (N);
1078 Traverse_Declarations_Or_Statements (Config_Pragmas (ADN));
1079 Traverse_Declarations_Or_Statements (Pragmas_After (ADN));
1081 -- Declarations and Actions do not correspond to source constructs,
1082 -- they contain only nodes from expansion, so at this point they
1083 -- should still be empty:
1085 pragma Assert (No (Declarations (ADN)));
1086 pragma Assert (No (Actions (ADN)));
1087 end Traverse_Aux_Decls;
1094 -- Start of processing for SCO_Record_Raw
1097 -- It is legitimate to run this pass multiple times (once per unit) so
1098 -- run it even if it was already run before.
1100 pragma Assert (SCO_Generation_State in None .. Raw);
1101 SCO_Generation_State := Raw;
1103 -- Ignore call if not generating code and generating SCO's
1105 if not (Generate_SCO and then Operating_Mode = Generate_Code) then
1109 -- Ignore call if this unit already recorded
1111 for J in 1 .. SCO_Unit_Number_Table.Last loop
1112 if U = SCO_Unit_Number_Table.Table (J) then
1117 -- Otherwise record starting entry
1119 From := SCO_Raw_Table.Last + 1;
1121 -- Get Unit (checking case of subunit)
1123 Lu := Unit (Cunit (U));
1125 if Nkind (Lu) = N_Subunit then
1126 Lu := Proper_Body (Lu);
1129 -- Traverse the unit
1131 Traverse_Aux_Decls (Cunit (U));
1134 when N_Generic_Instantiation |
1135 N_Generic_Package_Declaration |
1137 N_Package_Declaration |
1140 N_Subprogram_Declaration |
1142 Traverse_Declarations_Or_Statements (L => No_List, P => Lu);
1146 -- All other cases of compilation units (e.g. renamings), generate
1147 -- no SCO information.
1152 -- Make entry for new unit in unit tables, we will fill in the file
1153 -- name and dependency numbers later.
1155 SCO_Unit_Table.Append (
1158 File_Index => Get_Source_File_Index (Sloc (Lu)),
1160 To => SCO_Raw_Table.Last));
1162 SCO_Unit_Number_Table.Append (U);
1165 -----------------------
1166 -- Set_SCO_Condition --
1167 -----------------------
1169 procedure Set_SCO_Condition (Cond : Node_Id; Val : Boolean) is
1171 -- SCO annotations are not processed after the filtering pass
1173 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1175 Constant_Condition_Code : constant array (Boolean) of Character :=
1176 (False => 'f
', True => 't
');
1178 Orig : constant Node_Id := Original_Node (Cond);
1184 Sloc_Range (Orig, Start, Dummy);
1185 Index := SCO_Raw_Hash_Table.Get (Start);
1187 -- Index can be zero for boolean expressions that do not have SCOs
1188 -- (simple decisions outside of a control flow structure), or in case
1189 -- of a previous error.
1195 pragma Assert (SCO_Raw_Table.Table (Index).C1 = ' ');
1196 SCO_Raw_Table.Table (Index).C2 := Constant_Condition_Code (Val);
1198 end Set_SCO_Condition;
1200 ------------------------------
1201 -- Set_SCO_Logical_Operator --
1202 ------------------------------
1204 procedure Set_SCO_Logical_Operator (Op : Node_Id) is
1206 -- SCO annotations are not processed after the filtering pass
1208 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1210 Orig : constant Node_Id := Original_Node (Op);
1211 Orig_Sloc : constant Source_Ptr := Sloc (Orig);
1212 Index : constant Nat := SCO_Raw_Hash_Table.Get (Orig_Sloc);
1215 -- All (putative) logical operators are supposed to have their own entry
1216 -- in the SCOs table. However, the semantic analysis may invoke this
1217 -- subprogram with nodes that are out of the SCO generation scope.
1220 SCO_Raw_Table.Table (Index).C2 := ' ';
1222 end Set_SCO_Logical_Operator;
1224 ----------------------------
1225 -- Set_SCO_Pragma_Enabled --
1226 ----------------------------
1228 procedure Set_SCO_Pragma_Enabled (Loc : Source_Ptr) is
1230 -- SCO annotations are not processed after the filtering pass
1232 pragma Assert (not Generate_SCO or else SCO_Generation_State = Raw);
1237 -- Nothing to do if not generating SCO, or if we're not processing the
1238 -- original source occurrence of the pragma.
1240 if not (Generate_SCO
1241 and then In_Extended_Main_Source_Unit (Loc)
1242 and then not (In_Instance or In_Inlined_Body))
1247 -- Note: the reason we use the Sloc value as the key is that in the
1248 -- generic case, the call to this procedure is made on a copy of the
1249 -- original node, so we can't use the Node_Id value.
1251 Index := SCO_Raw_Hash_Table.Get (Loc);
1253 -- A zero index here indicates that semantic analysis found an
1254 -- activated pragma at Loc which does not have a corresponding pragma
1255 -- or aspect at the syntax level. This may occur in legitimate cases
1256 -- because of expanded code (such are Pre/Post conditions generated for
1257 -- formal parameter validity checks), or as a consequence of a previous
1265 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
1268 -- Note: may be called multiple times for the same sloc, so
1269 -- account for the fact that the entry may already have been
1273 -- Aspect (decision SCO)
1281 -- Pragma (statement SCO)
1284 pragma Assert (T.C2 = 'p
' or else T.C2 = 'P
');
1288 raise Program_Error;
1292 end Set_SCO_Pragma_Enabled;
1294 -------------------------
1295 -- Set_Raw_Table_Entry --
1296 -------------------------
1298 procedure Set_Raw_Table_Entry
1304 Pragma_Sloc : Source_Ptr := No_Location;
1305 Pragma_Aspect_Name : Name_Id := No_Name)
1307 pragma Assert (SCO_Generation_State = Raw);
1309 SCO_Raw_Table.Append
1312 From => To_Source_Location (From),
1313 To => To_Source_Location (To),
1315 Pragma_Sloc => Pragma_Sloc,
1316 Pragma_Aspect_Name => Pragma_Aspect_Name));
1317 end Set_Raw_Table_Entry;
1319 ------------------------
1320 -- To_Source_Location --
1321 ------------------------
1323 function To_Source_Location (S : Source_Ptr) return Source_Location is
1325 if S = No_Location then
1326 return No_Source_Location;
1329 (Line => Get_Logical_Line_Number (S),
1330 Col => Get_Column_Number (S));
1332 end To_Source_Location;
1334 -----------------------------------------
1335 -- Traverse_Declarations_Or_Statements --
1336 -----------------------------------------
1338 -- Tables used by Traverse_Declarations_Or_Statements for temporarily
1339 -- holding statement and decision entries. These are declared globally
1340 -- since they are shared by recursive calls to this procedure.
1342 type SC_Entry is record
1348 -- Used to store a single entry in the following table, From:To represents
1349 -- the range of entries in the CS line entry, and typ is the type, with
1350 -- space meaning that no type letter will accompany the entry.
1352 package SC is new Table.Table
1353 (Table_Component_Type => SC_Entry,
1354 Table_Index_Type => Nat,
1355 Table_Low_Bound => 1,
1356 Table_Initial => 1000,
1357 Table_Increment => 200,
1358 Table_Name => "SCO_SC");
1359 -- Used to store statement components for a CS entry to be output as a
1360 -- result of the call to this procedure. SC.Last is the last entry stored,
1361 -- so the current statement sequence is represented by SC_Array (SC_First
1362 -- .. SC.Last), where SC_First is saved on entry to each recursive call to
1365 -- Extend_Statement_Sequence adds an entry to this array, and then
1366 -- Set_Statement_Entry clears the entries starting with SC_First, copying
1367 -- these entries to the main SCO output table. The reason that we do the
1368 -- temporary caching of results in this array is that we want the SCO table
1369 -- entries for a given CS line to be contiguous, and the processing may
1370 -- output intermediate entries such as decision entries.
1372 type SD_Entry is record
1378 -- Used to store a single entry in the following table. Nod is the node to
1379 -- be searched for decisions for the case of Process_Decisions_Defer with a
1380 -- node argument (with Lst set to No_List. Lst is the list to be searched
1381 -- for decisions for the case of Process_Decisions_Defer with a List
1382 -- argument (in which case Nod is set to Empty). Plo is the sloc of the
1383 -- enclosing pragma, if any.
1385 package SD is new Table.Table
1386 (Table_Component_Type => SD_Entry,
1387 Table_Index_Type => Nat,
1388 Table_Low_Bound => 1,
1389 Table_Initial => 1000,
1390 Table_Increment => 200,
1391 Table_Name => "SCO_SD");
1392 -- Used to store possible decision information. Instead of calling the
1393 -- Process_Decisions procedures directly, we call Process_Decisions_Defer,
1394 -- which simply stores the arguments in this table. Then when we clear
1395 -- out a statement sequence using Set_Statement_Entry, after generating
1396 -- the CS lines for the statements, the entries in this table result in
1397 -- calls to Process_Decision. The reason for doing things this way is to
1398 -- ensure that decisions are output after the CS line for the statements
1399 -- in which the decisions occur.
1401 procedure Traverse_Declarations_Or_Statements
1403 D : Dominant_Info := No_Dominant;
1404 P : Node_Id := Empty)
1406 Discard_Dom : Dominant_Info;
1407 pragma Warnings (Off, Discard_Dom);
1409 Discard_Dom := Traverse_Declarations_Or_Statements (L, D, P);
1410 end Traverse_Declarations_Or_Statements;
1412 function Traverse_Declarations_Or_Statements
1414 D : Dominant_Info := No_Dominant;
1415 P : Node_Id := Empty) return Dominant_Info
1417 Current_Dominant : Dominant_Info := D;
1418 -- Dominance information for the current basic block
1420 Current_Test : Node_Id;
1421 -- Conditional node (N_If_Statement or N_Elsiif being processed
1425 SC_First : constant Nat := SC.Last + 1;
1426 SD_First : constant Nat := SD.Last + 1;
1427 -- Record first entries used in SC/SD at this recursive level
1429 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character);
1430 -- Extend the current statement sequence to encompass the node N. Typ
1431 -- is the letter that identifies the type of statement/declaration that
1432 -- is being added to the sequence.
1434 procedure Process_Decisions_Defer (N : Node_Id; T : Character);
1435 pragma Inline (Process_Decisions_Defer);
1436 -- This routine is logically the same as Process_Decisions, except that
1437 -- the arguments are saved in the SD table for later processing when
1438 -- Set_Statement_Entry is called, which goes through the saved entries
1439 -- making the corresponding calls to Process_Decision.
1441 procedure Process_Decisions_Defer (L : List_Id; T : Character);
1442 pragma Inline (Process_Decisions_Defer);
1443 -- Same case for list arguments, deferred call to Process_Decisions
1445 procedure Set_Statement_Entry;
1446 -- Output CS entries for all statements saved in table SC, and end the
1447 -- current CS sequence. Then output entries for all decisions nested in
1448 -- these statements, which have been deferred so far.
1450 procedure Traverse_One (N : Node_Id);
1451 -- Traverse one declaration or statement
1453 procedure Traverse_Aspects (N : Node_Id);
1454 -- Helper for Traverse_One: traverse N's aspect specifications
1456 -------------------------------
1457 -- Extend_Statement_Sequence --
1458 -------------------------------
1460 procedure Extend_Statement_Sequence (N : Node_Id; Typ : Character) is
1464 To_Node : Node_Id := Empty;
1467 Sloc_Range (N, F, T);
1470 when N_Accept_Statement =>
1471 if Present (Parameter_Specifications (N)) then
1472 To_Node := Last (Parameter_Specifications (N));
1473 elsif Present (Entry_Index (N)) then
1474 To_Node := Entry_Index (N);
1477 when N_Case_Statement =>
1478 To_Node := Expression (N);
1480 when N_If_Statement | N_Elsif_Part =>
1481 To_Node := Condition (N);
1483 when N_Extended_Return_Statement =>
1484 To_Node := Last (Return_Object_Declarations (N));
1486 when N_Loop_Statement =>
1487 To_Node := Iteration_Scheme (N);
1489 when N_Asynchronous_Select |
1490 N_Conditional_Entry_Call |
1491 N_Selective_Accept |
1492 N_Single_Protected_Declaration |
1493 N_Single_Task_Declaration |
1494 N_Timed_Entry_Call =>
1497 when N_Protected_Type_Declaration | N_Task_Type_Declaration =>
1498 if Has_Aspects (N) then
1499 To_Node := Last (Aspect_Specifications (N));
1501 elsif Present (Discriminant_Specifications (N)) then
1502 To_Node := Last (Discriminant_Specifications (N));
1505 To_Node := Defining_Identifier (N);
1513 if Present (To_Node) then
1514 Sloc_Range (To_Node, Dummy, T);
1517 SC.Append ((N, F, T, Typ));
1518 end Extend_Statement_Sequence;
1520 -----------------------------
1521 -- Process_Decisions_Defer --
1522 -----------------------------
1524 procedure Process_Decisions_Defer (N : Node_Id; T : Character) is
1526 SD.Append ((N, No_List, T, Current_Pragma_Sloc));
1527 end Process_Decisions_Defer;
1529 procedure Process_Decisions_Defer (L : List_Id; T : Character) is
1531 SD.Append ((Empty, L, T, Current_Pragma_Sloc));
1532 end Process_Decisions_Defer;
1534 -------------------------
1535 -- Set_Statement_Entry --
1536 -------------------------
1538 procedure Set_Statement_Entry is
1539 SC_Last : constant Int := SC.Last;
1540 SD_Last : constant Int := SD.Last;
1543 -- Output statement entries from saved entries in SC table
1545 for J in SC_First .. SC_Last loop
1546 if J = SC_First then
1548 if Current_Dominant /= No_Dominant then
1554 Sloc_Range (Current_Dominant.N, From, To);
1556 if Current_Dominant.K /= 'E
' then
1562 C2 => Current_Dominant.K,
1566 Pragma_Sloc => No_Location,
1567 Pragma_Aspect_Name => No_Name);
1573 SCE : SC_Entry renames SC.Table (J);
1574 Pragma_Sloc : Source_Ptr := No_Location;
1575 Pragma_Aspect_Name : Name_Id := No_Name;
1578 -- For the case of a statement SCO for a pragma controlled by
1579 -- Set_SCO_Pragma_Enabled, set Pragma_Sloc so that the SCO (and
1580 -- those of any nested decision) is emitted only if the pragma
1583 if SCE.Typ = 'p
' then
1584 Pragma_Sloc := SCE.From;
1585 SCO_Raw_Hash_Table.Set
1586 (Pragma_Sloc, SCO_Raw_Table.Last + 1);
1587 Pragma_Aspect_Name := Pragma_Name (SCE.N);
1588 pragma Assert (Pragma_Aspect_Name /= No_Name);
1590 elsif SCE.Typ = 'P
' then
1591 Pragma_Aspect_Name := Pragma_Name (SCE.N);
1592 pragma Assert (Pragma_Aspect_Name /= No_Name);
1600 Last => (J = SC_Last),
1601 Pragma_Sloc => Pragma_Sloc,
1602 Pragma_Aspect_Name => Pragma_Aspect_Name);
1606 -- Last statement of basic block, if present, becomes new current
1609 if SC_Last >= SC_First then
1610 Current_Dominant := ('S
', SC.Table (SC_Last).N);
1613 -- Clear out used section of SC table
1615 SC.Set_Last (SC_First - 1);
1617 -- Output any embedded decisions
1619 for J in SD_First .. SD_Last loop
1621 SDE : SD_Entry renames SD.Table (J);
1624 if Present (SDE.Nod) then
1625 Process_Decisions (SDE.Nod, SDE.Typ, SDE.Plo);
1627 Process_Decisions (SDE.Lst, SDE.Typ, SDE.Plo);
1632 -- Clear out used section of SD table
1634 SD.Set_Last (SD_First - 1);
1635 end Set_Statement_Entry;
1637 ----------------------
1638 -- Traverse_Aspects --
1639 ----------------------
1641 procedure Traverse_Aspects (N : Node_Id) is
1647 AN := First (Aspect_Specifications (N));
1648 while Present (AN) loop
1649 AE := Expression (AN);
1651 -- SCOs are generated before semantic analysis/expansion:
1652 -- PPCs are not split yet.
1654 pragma Assert (not Split_PPC (AN));
1658 case Get_Aspect_Id (AN) is
1660 -- Aspects rewritten into pragmas controlled by a Check_Policy:
1661 -- Current_Pragma_Sloc must be set to the sloc of the aspect
1662 -- specification. The corresponding pragma will have the same
1665 when Aspect_Invariant |
1667 Aspect_Postcondition |
1669 Aspect_Precondition |
1670 Aspect_Type_Invariant =>
1673 -- Aspects whose checks are generated in client units,
1674 -- regardless of whether or not the check is activated in the
1675 -- unit which contains the declaration: create decision as
1676 -- unconditionally enabled aspect (but still make a pragma
1677 -- entry since Set_SCO_Pragma_Enabled will be called when
1678 -- analyzing actual checks, possibly in other units).
1680 -- Pre/post can have checks in client units too because of
1681 -- inheritance, so should they be moved here???
1683 when Aspect_Dynamic_Predicate |
1685 Aspect_Static_Predicate =>
1688 -- Other aspects: just process any decision nested in the
1689 -- aspect expression.
1692 if Has_Decision (AE) then
1698 if C1 /= ASCII.NUL then
1699 pragma Assert (Current_Pragma_Sloc = No_Location);
1701 if C1 = 'a
' or else C1 = 'A
' then
1702 Current_Pragma_Sloc := Sloc (AN);
1705 Process_Decisions_Defer (AE, C1);
1707 Current_Pragma_Sloc := No_Location;
1712 end Traverse_Aspects;
1718 procedure Traverse_One (N : Node_Id) is
1720 -- Initialize or extend current statement sequence. Note that for
1721 -- special cases such as IF and Case statements we will modify
1722 -- the range to exclude internal statements that should not be
1723 -- counted as part of the current statement sequence.
1727 -- Package declaration
1729 when N_Package_Declaration =>
1730 Set_Statement_Entry;
1731 Traverse_Package_Declaration (N, Current_Dominant);
1733 -- Generic package declaration
1735 when N_Generic_Package_Declaration =>
1736 Set_Statement_Entry;
1737 Traverse_Generic_Package_Declaration (N);
1741 when N_Package_Body =>
1742 Set_Statement_Entry;
1743 Traverse_Package_Body (N);
1745 -- Subprogram declaration or subprogram body stub
1747 when N_Subprogram_Declaration | N_Subprogram_Body_Stub =>
1748 Process_Decisions_Defer
1749 (Parameter_Specifications (Specification (N)), 'X
');
1751 -- Entry declaration
1753 when N_Entry_Declaration =>
1754 Process_Decisions_Defer (Parameter_Specifications (N), 'X
');
1756 -- Generic subprogram declaration
1758 when N_Generic_Subprogram_Declaration =>
1759 Process_Decisions_Defer
1760 (Generic_Formal_Declarations (N), 'X
');
1761 Process_Decisions_Defer
1762 (Parameter_Specifications (Specification (N)), 'X
');
1764 -- Task or subprogram body
1766 when N_Task_Body | N_Subprogram_Body =>
1767 Set_Statement_Entry;
1768 Traverse_Subprogram_Or_Task_Body (N);
1772 when N_Entry_Body =>
1774 Cond : constant Node_Id :=
1775 Condition (Entry_Body_Formal_Part (N));
1777 Inner_Dominant : Dominant_Info := No_Dominant;
1780 Set_Statement_Entry;
1782 if Present (Cond) then
1783 Process_Decisions_Defer (Cond, 'G
');
1785 -- For an entry body with a barrier, the entry body
1786 -- is dominanted by a True evaluation of the barrier.
1788 Inner_Dominant := ('T
', N);
1791 Traverse_Subprogram_Or_Task_Body (N, Inner_Dominant);
1796 when N_Protected_Body =>
1797 Set_Statement_Entry;
1798 Traverse_Declarations_Or_Statements (Declarations (N));
1800 -- Exit statement, which is an exit statement in the SCO sense,
1801 -- so it is included in the current statement sequence, but
1802 -- then it terminates this sequence. We also have to process
1803 -- any decisions in the exit statement expression.
1805 when N_Exit_Statement =>
1806 Extend_Statement_Sequence (N, 'E
');
1807 Process_Decisions_Defer (Condition (N), 'E
');
1808 Set_Statement_Entry;
1810 -- If condition is present, then following statement is
1811 -- only executed if the condition evaluates to False.
1813 if Present (Condition (N)) then
1814 Current_Dominant := ('F
', N);
1816 Current_Dominant := No_Dominant;
1819 -- Label, which breaks the current statement sequence, but the
1820 -- label itself is not included in the next statement sequence,
1821 -- since it generates no code.
1824 Set_Statement_Entry;
1825 Current_Dominant := No_Dominant;
1827 -- Block statement, which breaks the current statement sequence
1829 when N_Block_Statement =>
1830 Set_Statement_Entry;
1832 -- The first statement in the handled sequence of statements
1833 -- is dominated by the elaboration of the last declaration.
1835 Current_Dominant := Traverse_Declarations_Or_Statements
1836 (L => Declarations (N),
1837 D => Current_Dominant);
1839 Traverse_Handled_Statement_Sequence
1840 (N => Handled_Statement_Sequence (N),
1841 D => Current_Dominant);
1843 -- If statement, which breaks the current statement sequence,
1844 -- but we include the condition in the current sequence.
1846 when N_If_Statement =>
1848 Extend_Statement_Sequence (N, 'I
');
1849 Process_Decisions_Defer (Condition (N), 'I
');
1850 Set_Statement_Entry;
1852 -- Now we traverse the statements in the THEN part
1854 Traverse_Declarations_Or_Statements
1855 (L => Then_Statements (N),
1858 -- Loop through ELSIF parts if present
1860 if Present (Elsif_Parts (N)) then
1862 Saved_Dominant : constant Dominant_Info :=
1865 Elif : Node_Id := First (Elsif_Parts (N));
1868 while Present (Elif) loop
1870 -- An Elsif is executed only if the previous test
1871 -- got a FALSE outcome.
1873 Current_Dominant := ('F
', Current_Test);
1875 -- Now update current test information
1877 Current_Test := Elif;
1879 -- We generate a statement sequence for the
1880 -- construct "ELSIF condition", so that we have
1881 -- a statement for the resulting decisions.
1883 Extend_Statement_Sequence (Elif, 'I
');
1884 Process_Decisions_Defer (Condition (Elif), 'I
');
1885 Set_Statement_Entry;
1887 -- An ELSIF part is never guaranteed to have
1888 -- been executed, following statements are only
1889 -- dominated by the initial IF statement.
1891 Current_Dominant := Saved_Dominant;
1893 -- Traverse the statements in the ELSIF
1895 Traverse_Declarations_Or_Statements
1896 (L => Then_Statements (Elif),
1903 -- Finally traverse the ELSE statements if present
1905 Traverse_Declarations_Or_Statements
1906 (L => Else_Statements (N),
1907 D => ('F
', Current_Test));
1909 -- CASE statement, which breaks the current statement sequence,
1910 -- but we include the expression in the current sequence.
1912 when N_Case_Statement =>
1913 Extend_Statement_Sequence (N, 'C
');
1914 Process_Decisions_Defer (Expression (N), 'X
');
1915 Set_Statement_Entry;
1917 -- Process case branches, all of which are dominated by the
1923 Alt := First_Non_Pragma (Alternatives (N));
1924 while Present (Alt) loop
1925 Traverse_Declarations_Or_Statements
1926 (L => Statements (Alt),
1927 D => Current_Dominant);
1934 when N_Accept_Statement =>
1935 Extend_Statement_Sequence (N, 'A
');
1936 Set_Statement_Entry;
1938 -- Process sequence of statements, dominant is the ACCEPT
1941 Traverse_Handled_Statement_Sequence
1942 (N => Handled_Statement_Sequence (N),
1943 D => Current_Dominant);
1947 when N_Selective_Accept =>
1948 Extend_Statement_Sequence (N, 'S
');
1949 Set_Statement_Entry;
1951 -- Process alternatives
1956 S_Dom : Dominant_Info;
1959 Alt := First (Select_Alternatives (N));
1960 while Present (Alt) loop
1961 S_Dom := Current_Dominant;
1962 Guard := Condition (Alt);
1964 if Present (Guard) then
1968 Pragma_Sloc => No_Location);
1969 Current_Dominant := ('T
', Guard);
1974 Current_Dominant := S_Dom;
1979 Traverse_Declarations_Or_Statements
1980 (L => Else_Statements (N),
1981 D => Current_Dominant);
1983 when N_Timed_Entry_Call | N_Conditional_Entry_Call =>
1984 Extend_Statement_Sequence (N, 'S
');
1985 Set_Statement_Entry;
1987 -- Process alternatives
1989 Traverse_One (Entry_Call_Alternative (N));
1991 if Nkind (N) = N_Timed_Entry_Call then
1992 Traverse_One (Delay_Alternative (N));
1994 Traverse_Declarations_Or_Statements
1995 (L => Else_Statements (N),
1996 D => Current_Dominant);
1999 when N_Asynchronous_Select =>
2000 Extend_Statement_Sequence (N, 'S
');
2001 Set_Statement_Entry;
2003 Traverse_One (Triggering_Alternative (N));
2004 Traverse_Declarations_Or_Statements
2005 (L => Statements (Abortable_Part (N)),
2006 D => Current_Dominant);
2008 when N_Accept_Alternative =>
2009 Traverse_Declarations_Or_Statements
2010 (L => Statements (N),
2011 D => Current_Dominant,
2012 P => Accept_Statement (N));
2014 when N_Entry_Call_Alternative =>
2015 Traverse_Declarations_Or_Statements
2016 (L => Statements (N),
2017 D => Current_Dominant,
2018 P => Entry_Call_Statement (N));
2020 when N_Delay_Alternative =>
2021 Traverse_Declarations_Or_Statements
2022 (L => Statements (N),
2023 D => Current_Dominant,
2024 P => Delay_Statement (N));
2026 when N_Triggering_Alternative =>
2027 Traverse_Declarations_Or_Statements
2028 (L => Statements (N),
2029 D => Current_Dominant,
2030 P => Triggering_Statement (N));
2032 when N_Terminate_Alternative =>
2034 -- It is dubious to emit a statement SCO for a TERMINATE
2035 -- alternative, since no code is actually executed if the
2036 -- alternative is selected -- the tasking runtime call just
2039 Extend_Statement_Sequence (N, ' ');
2040 Set_Statement_Entry;
2042 -- Unconditional exit points, which are included in the current
2043 -- statement sequence, but then terminate it
2045 when N_Requeue_Statement |
2047 N_Raise_Statement =>
2048 Extend_Statement_Sequence (N, ' ');
2049 Set_Statement_Entry;
2050 Current_Dominant := No_Dominant;
2052 -- Simple return statement. which is an exit point, but we
2053 -- have to process the return expression for decisions.
2055 when N_Simple_Return_Statement =>
2056 Extend_Statement_Sequence (N, ' ');
2057 Process_Decisions_Defer (Expression (N), 'X
');
2058 Set_Statement_Entry;
2059 Current_Dominant := No_Dominant;
2061 -- Extended return statement
2063 when N_Extended_Return_Statement =>
2064 Extend_Statement_Sequence (N, 'R
');
2065 Process_Decisions_Defer (Return_Object_Declarations (N), 'X
');
2066 Set_Statement_Entry;
2068 Traverse_Handled_Statement_Sequence
2069 (N => Handled_Statement_Sequence (N),
2070 D => Current_Dominant);
2072 Current_Dominant := No_Dominant;
2074 -- Loop ends the current statement sequence, but we include
2075 -- the iteration scheme if present in the current sequence.
2076 -- But the body of the loop starts a new sequence, since it
2077 -- may not be executed as part of the current sequence.
2079 when N_Loop_Statement =>
2081 ISC : constant Node_Id := Iteration_Scheme (N);
2082 Inner_Dominant : Dominant_Info := No_Dominant;
2085 if Present (ISC) then
2087 -- If iteration scheme present, extend the current
2088 -- statement sequence to include the iteration scheme
2089 -- and process any decisions it contains.
2093 if Present (Condition (ISC)) then
2094 Extend_Statement_Sequence (N, 'W
');
2095 Process_Decisions_Defer (Condition (ISC), 'W
');
2097 -- Set more specific dominant for inner statements
2098 -- (the control sloc for the decision is that of
2099 -- the WHILE token).
2101 Inner_Dominant := ('T
', ISC);
2106 Extend_Statement_Sequence (N, 'F
');
2107 Process_Decisions_Defer
2108 (Loop_Parameter_Specification (ISC), 'X
');
2112 Set_Statement_Entry;
2114 if Inner_Dominant = No_Dominant then
2115 Inner_Dominant := Current_Dominant;
2118 Traverse_Declarations_Or_Statements
2119 (L => Statements (N),
2120 D => Inner_Dominant);
2127 -- Record sloc of pragma (pragmas don't nest)
2129 pragma Assert (Current_Pragma_Sloc = No_Location);
2130 Current_Pragma_Sloc := Sloc (N);
2132 -- Processing depends on the kind of pragma
2135 Nam : constant Name_Id := Pragma_Name (N);
2137 First (Pragma_Argument_Associations (N));
2143 Name_Assert_And_Cut |
2146 Name_Loop_Invariant |
2147 Name_Postcondition |
2148 Name_Precondition =>
2150 -- For Assert/Check/Precondition/Postcondition, we
2151 -- must generate a P entry for the decision. Note
2152 -- that this is done unconditionally at this stage.
2153 -- Output for disabled pragmas is suppressed later
2154 -- on when we output the decision line in Put_SCOs,
2155 -- depending on setting by Set_SCO_Pragma_Enabled.
2157 if Nam = Name_Check then
2161 Process_Decisions_Defer (Expression (Arg), 'P
');
2164 -- Pre/postconditions can be inherited so SCO should
2165 -- never be deactivated???
2168 if Present (Arg) and then Present (Next (Arg)) then
2170 -- Case of a dyadic pragma Debug: first argument
2171 -- is a P decision, any nested decision in the
2172 -- second argument is an X decision.
2174 Process_Decisions_Defer (Expression (Arg), 'P
');
2178 Process_Decisions_Defer (Expression (Arg), 'X
');
2181 -- For all other pragmas, we generate decision entries
2182 -- for any embedded expressions, and the pragma is
2185 -- Should generate P decisions (not X) for assertion
2186 -- related pragmas: [Type_]Invariant,
2187 -- [{Static,Dynamic}_]Predicate???
2190 Process_Decisions_Defer (N, 'X
');
2194 -- Add statement SCO
2196 Extend_Statement_Sequence (N, Typ);
2198 Current_Pragma_Sloc := No_Location;
2201 -- Object declaration. Ignored if Prev_Ids is set, since the
2202 -- parser generates multiple instances of the whole declaration
2203 -- if there is more than one identifier declared, and we only
2204 -- want one entry in the SCOs, so we take the first, for which
2205 -- Prev_Ids is False.
2207 when N_Object_Declaration | N_Number_Declaration =>
2208 if not Prev_Ids (N) then
2209 Extend_Statement_Sequence (N, 'o
');
2211 if Has_Decision (N) then
2212 Process_Decisions_Defer (N, 'X
');
2216 -- All other cases, which extend the current statement sequence
2217 -- but do not terminate it, even if they have nested decisions.
2219 when N_Protected_Type_Declaration | N_Task_Type_Declaration =>
2220 Extend_Statement_Sequence (N, 't
');
2221 Process_Decisions_Defer (Discriminant_Specifications (N), 'X
');
2222 Set_Statement_Entry;
2224 Traverse_Sync_Definition (N);
2226 when N_Single_Protected_Declaration | N_Single_Task_Declaration =>
2227 Extend_Statement_Sequence (N, 'o
');
2228 Set_Statement_Entry;
2230 Traverse_Sync_Definition (N);
2234 -- Determine required type character code, or ASCII.NUL if
2235 -- no SCO should be generated for this node.
2238 NK : constant Node_Kind := Nkind (N);
2243 when N_Full_Type_Declaration |
2244 N_Incomplete_Type_Declaration |
2245 N_Private_Extension_Declaration |
2246 N_Private_Type_Declaration =>
2249 when N_Subtype_Declaration =>
2252 when N_Renaming_Declaration =>
2255 when N_Generic_Instantiation =>
2258 when N_Package_Body_Stub |
2259 N_Protected_Body_Stub |
2260 N_Representation_Clause |
2262 N_Use_Package_Clause |
2263 N_Use_Type_Clause =>
2266 when N_Procedure_Call_Statement =>
2270 if NK in N_Statement_Other_Than_Procedure_Call then
2277 if Typ /= ASCII.NUL then
2278 Extend_Statement_Sequence (N, Typ);
2282 -- Process any embedded decisions
2284 if Has_Decision (N) then
2285 Process_Decisions_Defer (N, 'X
');
2289 -- Process aspects if present
2291 Traverse_Aspects (N);
2294 -- Start of processing for Traverse_Declarations_Or_Statements
2297 -- Process single prefixed node
2303 -- Loop through statements or declarations
2305 if Is_Non_Empty_List (L) then
2307 while Present (N) loop
2309 -- Note: For separate bodies, we see the tree after Par.Labl has
2310 -- introduced implicit labels, so we need to ignore those nodes.
2312 if Nkind (N) /= N_Implicit_Label_Declaration then
2321 -- End sequence of statements and flush deferred decisions
2323 if Present (P) or else Is_Non_Empty_List (L) then
2324 Set_Statement_Entry;
2327 return Current_Dominant;
2328 end Traverse_Declarations_Or_Statements;
2330 ------------------------------------------
2331 -- Traverse_Generic_Package_Declaration --
2332 ------------------------------------------
2334 procedure Traverse_Generic_Package_Declaration (N : Node_Id) is
2336 Process_Decisions (Generic_Formal_Declarations (N), 'X
', No_Location);
2337 Traverse_Package_Declaration (N);
2338 end Traverse_Generic_Package_Declaration;
2340 -----------------------------------------
2341 -- Traverse_Handled_Statement_Sequence --
2342 -----------------------------------------
2344 procedure Traverse_Handled_Statement_Sequence
2346 D : Dominant_Info := No_Dominant)
2351 -- For package bodies without a statement part, the parser adds an empty
2352 -- one, to normalize the representation. The null statement therein,
2353 -- which does not come from source, does not get a SCO.
2355 if Present (N) and then Comes_From_Source (N) then
2356 Traverse_Declarations_Or_Statements (Statements (N), D);
2358 if Present (Exception_Handlers (N)) then
2359 Handler := First_Non_Pragma (Exception_Handlers (N));
2360 while Present (Handler) loop
2361 Traverse_Declarations_Or_Statements
2362 (L => Statements (Handler),
2363 D => ('E
', Handler));
2368 end Traverse_Handled_Statement_Sequence;
2370 ---------------------------
2371 -- Traverse_Package_Body --
2372 ---------------------------
2374 procedure Traverse_Package_Body (N : Node_Id) is
2375 Dom : Dominant_Info;
2377 -- The first statement in the handled sequence of statements is
2378 -- dominated by the elaboration of the last declaration.
2380 Dom := Traverse_Declarations_Or_Statements (Declarations (N));
2382 Traverse_Handled_Statement_Sequence
2383 (Handled_Statement_Sequence (N), Dom);
2384 end Traverse_Package_Body;
2386 ----------------------------------
2387 -- Traverse_Package_Declaration --
2388 ----------------------------------
2390 procedure Traverse_Package_Declaration
2392 D : Dominant_Info := No_Dominant)
2394 Spec : constant Node_Id := Specification (N);
2395 Dom : Dominant_Info;
2399 Traverse_Declarations_Or_Statements (Visible_Declarations (Spec), D);
2401 -- First private declaration is dominated by last visible declaration
2403 Traverse_Declarations_Or_Statements (Private_Declarations (Spec), Dom);
2404 end Traverse_Package_Declaration;
2406 ------------------------------
2407 -- Traverse_Sync_Definition --
2408 ------------------------------
2410 procedure Traverse_Sync_Definition (N : Node_Id) is
2411 Dom_Info : Dominant_Info := ('S
', N);
2412 -- The first declaration is dominated by the protected or task [type]
2416 -- N's protected or task definition
2418 Priv_Decl : List_Id;
2420 -- Sync_Def's Visible_Declarations and Private_Declarations
2424 when N_Protected_Type_Declaration |
2425 N_Single_Protected_Declaration =>
2426 Sync_Def := Protected_Definition (N);
2428 when N_Single_Task_Declaration |
2429 N_Task_Type_Declaration =>
2430 Sync_Def := Task_Definition (N);
2433 raise Program_Error;
2436 -- Sync_Def may be Empty at least for empty Task_Type_Declarations.
2437 -- Querying Visible or Private_Declarations is invalid in this case.
2439 if Present (Sync_Def) then
2440 Vis_Decl := Visible_Declarations (Sync_Def);
2441 Priv_Decl := Private_Declarations (Sync_Def);
2443 Vis_Decl := No_List;
2444 Priv_Decl := No_List;
2447 Dom_Info := Traverse_Declarations_Or_Statements
2451 -- If visible declarations are present, the first private declaration
2452 -- is dominated by the last visible declaration.
2454 Traverse_Declarations_Or_Statements
2457 end Traverse_Sync_Definition;
2459 --------------------------------------
2460 -- Traverse_Subprogram_Or_Task_Body --
2461 --------------------------------------
2463 procedure Traverse_Subprogram_Or_Task_Body
2465 D : Dominant_Info := No_Dominant)
2467 Decls : constant List_Id := Declarations (N);
2468 Dom_Info : Dominant_Info := D;
2471 -- If declarations are present, the first statement is dominated by the
2472 -- last declaration.
2474 Dom_Info := Traverse_Declarations_Or_Statements
2475 (L => Decls, D => Dom_Info);
2477 Traverse_Handled_Statement_Sequence
2478 (N => Handled_Statement_Sequence (N),
2480 end Traverse_Subprogram_Or_Task_Body;
2482 -------------------------
2483 -- SCO_Record_Filtered --
2484 -------------------------
2486 procedure SCO_Record_Filtered is
2487 type Decision is record
2489 -- Type of the SCO decision (see comments for SCO_Table_Entry.C1)
2491 Sloc : Source_Location;
2494 -- Index in the SCO_Raw_Table for the root operator/condition for the
2495 -- expression that controls the decision.
2497 -- Decision descriptor: used to gather information about a candidate
2500 package Pending_Decisions is new Table.Table
2501 (Table_Component_Type => Decision,
2502 Table_Index_Type => Nat,
2503 Table_Low_Bound => 1,
2504 Table_Initial => 1000,
2505 Table_Increment => 200,
2506 Table_Name => "Filter_Pending_Decisions");
2507 -- Table used to hold decisions to process during the collection pass
2509 procedure Add_Expression_Tree (Idx : in out Nat);
2510 -- Add SCO raw table entries for the decision controlling expression
2511 -- tree starting at Idx to the filtered SCO table.
2513 procedure Collect_Decisions
2516 -- Collect decisions to add to the filtered SCO table starting at the
2517 -- D decision (including it and its nested operators/conditions). Set
2518 -- Next to the first node index passed the whole decision.
2520 procedure Compute_Range
2522 From : out Source_Location;
2523 To : out Source_Location);
2524 -- Compute the source location range for the expression tree starting at
2525 -- Idx in the SCO raw table. Store its bounds in From and To.
2527 function Is_Decision (Idx : Nat) return Boolean;
2528 -- Return if the expression tree starting at Idx has adjacent nested
2529 -- nodes that make a decision.
2531 procedure Process_Pending_Decisions
2532 (Original_Decision : SCO_Table_Entry);
2533 -- Complete the filtered SCO table using collected decisions. Output
2534 -- decisions inherit the pragma information from the original decision.
2536 procedure Search_Nested_Decisions (Idx : in out Nat);
2537 -- Collect decisions to add to the filtered SCO table starting at the
2538 -- node at Idx in the SCO raw table. This node must not be part of an
2539 -- already-processed decision. Set Idx to the first node index passed
2540 -- the whole expression tree.
2542 procedure Skip_Decision
2544 Process_Nested_Decisions : Boolean);
2545 -- Skip all the nodes that belong to the decision starting at Idx. If
2546 -- Process_Nested_Decision, call Search_Nested_Decisions on the first
2547 -- nested nodes that do not belong to the decision. Set Idx to the first
2548 -- node index passed the whole expression tree.
2550 -------------------------
2551 -- Add_Expression_Tree --
2552 -------------------------
2554 procedure Add_Expression_Tree (Idx : in out Nat) is
2555 Node_Idx : constant Nat := Idx;
2556 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Node_Idx);
2557 From : Source_Location;
2558 To : Source_Location;
2564 -- This is a single condition. Add an entry for it and move on
2566 SCO_Table.Append (T);
2571 -- This is a NOT operator: add an entry for it and browse its
2574 SCO_Table.Append (T);
2576 Add_Expression_Tree (Idx);
2580 -- This must be an AND/OR/AND THEN/OR ELSE operator
2584 -- This is not a short circuit operator: consider this one
2585 -- and all its children as a single condition.
2587 Compute_Range (Idx, From, To);
2594 Pragma_Sloc => No_Location,
2595 Pragma_Aspect_Name => No_Name));
2598 -- This is a real short circuit operator: add an entry for
2599 -- it and browse its children.
2601 SCO_Table.Append (T);
2603 Add_Expression_Tree (Idx);
2604 Add_Expression_Tree (Idx);
2607 end Add_Expression_Tree;
2609 -----------------------
2610 -- Collect_Decisions --
2611 -----------------------
2613 procedure Collect_Decisions
2620 if D.Kind /= 'X
' or else Is_Decision (D.Top) then
2621 Pending_Decisions.Append (D);
2624 Skip_Decision (Idx, True);
2626 end Collect_Decisions;
2632 procedure Compute_Range
2634 From : out Source_Location;
2635 To : out Source_Location)
2637 Sloc_F : Source_Location := No_Source_Location;
2638 Sloc_T : Source_Location := No_Source_Location;
2640 procedure Process_One;
2641 -- Process one node of the tree, and recurse over children. Update
2642 -- Idx during the traversal.
2648 procedure Process_One is
2650 if Sloc_F = No_Source_Location
2652 SCO_Raw_Table.Table (Idx).From < Sloc_F
2654 Sloc_F := SCO_Raw_Table.Table (Idx).From;
2657 if Sloc_T = No_Source_Location
2659 Sloc_T < SCO_Raw_Table.Table (Idx).To
2661 Sloc_T := SCO_Raw_Table.Table (Idx).To;
2664 if SCO_Raw_Table.Table (Idx).C1 = ' ' then
2666 -- This is a condition: nothing special to do
2670 elsif SCO_Raw_Table.Table (Idx).C1 = '!' then
2672 -- The "not" operator has only one operand
2678 -- This is an AND THEN or OR ELSE logical operator: follow the
2679 -- left, then the right operands.
2688 -- Start of processing for Compute_Range
2700 function Is_Decision (Idx : Nat) return Boolean is
2706 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Index);
2715 -- This is a decision iff the only operand of the NOT
2716 -- operator could be a standalone decision.
2722 -- This node is a logical operator (and thus could be a
2723 -- standalone decision) iff it is a short circuit
2733 -------------------------------
2734 -- Process_Pending_Decisions --
2735 -------------------------------
2737 procedure Process_Pending_Decisions
2738 (Original_Decision : SCO_Table_Entry)
2741 for Index in 1 .. Pending_Decisions.Last loop
2743 D : Decision renames Pending_Decisions.Table (Index);
2747 -- Add a SCO table entry for the decision itself
2749 pragma Assert (D.Kind /= ' ');
2752 ((To => No_Source_Location,
2757 Pragma_Sloc => Original_Decision.Pragma_Sloc,
2758 Pragma_Aspect_Name =>
2759 Original_Decision.Pragma_Aspect_Name));
2761 -- Then add ones for its nested operators/operands. Do not
2762 -- forget to tag its *last* entry as such.
2764 Add_Expression_Tree (Idx);
2765 SCO_Table.Table (SCO_Table.Last).Last := True;
2769 -- Clear the pending decisions list
2770 Pending_Decisions.Set_Last (0);
2771 end Process_Pending_Decisions;
2773 -----------------------------
2774 -- Search_Nested_Decisions --
2775 -----------------------------
2777 procedure Search_Nested_Decisions (Idx : in out Nat) is
2781 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2800 -- This is not a logical operator: start looking for
2801 -- nested decisions from here. Recurse over the left
2802 -- child and let the loop take care of the right one.
2805 Search_Nested_Decisions (Idx);
2808 -- We found a nested decision
2820 end Search_Nested_Decisions;
2826 procedure Skip_Decision
2828 Process_Nested_Decisions : Boolean)
2833 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2844 -- This NOT operator belongs to the outside decision:
2850 if T.C2 = '?
' and then Process_Nested_Decisions then
2852 -- This is not a logical operator: start looking for
2853 -- nested decisions from here. Recurse over the left
2854 -- child and let the loop take care of the right one.
2856 Search_Nested_Decisions (Idx);
2859 -- This is a logical operator, so it belongs to the
2860 -- outside decision: skip its left child, then let the
2861 -- loop take care of the right one.
2863 Skip_Decision (Idx, Process_Nested_Decisions);
2870 -- Start of processing for SCO_Record_Filtered
2873 -- Filtering must happen only once: do nothing if it this pass was
2876 if SCO_Generation_State = Filtered then
2879 pragma Assert (SCO_Generation_State = Raw);
2880 SCO_Generation_State := Filtered;
2883 -- Loop through all SCO entries under SCO units
2885 for Unit_Idx in 1 .. SCO_Unit_Table.Last loop
2887 Unit : SCO_Unit_Table_Entry
2888 renames SCO_Unit_Table.Table (Unit_Idx);
2890 Idx : Nat := Unit.From;
2891 -- Index of the current SCO raw table entry
2893 New_From : constant Nat := SCO_Table.Last + 1;
2894 -- After copying SCO enties of interest to the final table, we
2895 -- will have to change the From/To indexes this unit targets.
2896 -- This constant keeps track of the new From index.
2899 while Idx <= Unit.To loop
2901 T : SCO_Table_Entry renames SCO_Raw_Table.Table (Idx);
2906 -- Decision (of any kind, including pragmas and aspects)
2908 when 'E
' | 'G
' | 'I
' | 'W
' | 'X
' | 'P
' | 'a
' | 'A
' =>
2909 if SCO_Pragma_Disabled (T.Pragma_Sloc) then
2911 -- Skip SCO entries for decisions in disabled
2912 -- constructs (pragmas or aspects).
2915 Skip_Decision (Idx, False);
2923 Process_Pending_Decisions (T);
2926 -- There is no translation/filtering to do for other kind
2927 -- of SCO items (statements, dominance markers, etc.).
2929 when '|
' | '&' | '!' | ' ' =>
2931 -- SCO logical operators and conditions cannot exist
2932 -- on their own: they must be inside a decision (such
2933 -- entries must have been skipped by
2934 -- Collect_Decisions).
2936 raise Program_Error;
2939 SCO_Table.Append (T);
2945 -- Now, update the SCO entry indexes in the unit entry
2947 Unit.From := New_From;
2948 Unit.To := SCO_Table.Last;
2952 -- Then clear the raw table to free bytes
2955 end SCO_Record_Filtered;