1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                             S E M _ P R A G                              --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2021, 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------------------------------------------------------------------------------
25
26--  Pragma handling is isolated in a separate package
27--  (logically this processing belongs in chapter 4)
28
29with Namet;  use Namet;
30with Opt;    use Opt;
31with Snames; use Snames;
32with Types;  use Types;
33
34package Sem_Prag is
35
36   --  The following table lists all pragmas that emulate an Ada 2012 aspect
37
38   Aspect_Specifying_Pragma : constant array (Pragma_Id) of Boolean :=
39     (Pragma_Abstract_State               => True,
40      Pragma_All_Calls_Remote             => True,
41      Pragma_Annotate                     => True,
42      Pragma_Async_Readers                => True,
43      Pragma_Async_Writers                => True,
44      Pragma_Asynchronous                 => True,
45      Pragma_Atomic                       => True,
46      Pragma_Atomic_Components            => True,
47      Pragma_Attach_Handler               => True,
48      Pragma_Constant_After_Elaboration   => True,
49      Pragma_Contract_Cases               => True,
50      Pragma_Convention                   => True,
51      Pragma_CPU                          => True,
52      Pragma_CUDA_Device                  => True,
53      Pragma_CUDA_Global                  => True,
54      Pragma_Default_Initial_Condition    => True,
55      Pragma_Default_Storage_Pool         => True,
56      Pragma_Depends                      => True,
57      Pragma_Discard_Names                => True,
58      Pragma_Dispatching_Domain           => True,
59      Pragma_Effective_Reads              => True,
60      Pragma_Effective_Writes             => True,
61      Pragma_Elaborate_Body               => True,
62      Pragma_Export                       => True,
63      Pragma_Extensions_Visible           => True,
64      Pragma_Favor_Top_Level              => True,
65      Pragma_Ghost                        => True,
66      Pragma_Global                       => True,
67      Pragma_GNAT_Annotate                => True,
68      Pragma_Import                       => True,
69      Pragma_Independent                  => True,
70      Pragma_Independent_Components       => True,
71      Pragma_Initial_Condition            => True,
72      Pragma_Initializes                  => True,
73      Pragma_Inline                       => True,
74      Pragma_Inline_Always                => True,
75      Pragma_Interrupt_Handler            => True,
76      Pragma_Interrupt_Priority           => True,
77      Pragma_Invariant                    => True,
78      Pragma_Linker_Section               => True,
79      Pragma_Lock_Free                    => True,
80      Pragma_No_Elaboration_Code_All      => True,
81      Pragma_No_Return                    => True,
82      Pragma_Obsolescent                  => True,
83      Pragma_Pack                         => True,
84      Pragma_Part_Of                      => True,
85      Pragma_Persistent_BSS               => True,
86      Pragma_Post                         => True,
87      Pragma_Post_Class                   => True,
88      Pragma_Postcondition                => True,
89      Pragma_Pre                          => True,
90      Pragma_Pre_Class                    => True,
91      Pragma_Precondition                 => True,
92      Pragma_Predicate                    => True,
93      Pragma_Preelaborable_Initialization => True,
94      Pragma_Preelaborate                 => True,
95      Pragma_Priority                     => True,
96      Pragma_Pure                         => True,
97      Pragma_Pure_Function                => True,
98      Pragma_Refined_Depends              => True,
99      Pragma_Refined_Global               => True,
100      Pragma_Refined_Post                 => True,
101      Pragma_Refined_State                => True,
102      Pragma_Relative_Deadline            => True,
103      Pragma_Remote_Access_Type           => True,
104      Pragma_Remote_Call_Interface        => True,
105      Pragma_Remote_Types                 => True,
106      Pragma_Secondary_Stack_Size         => True,
107      Pragma_Shared                       => True,
108      Pragma_Shared_Passive               => True,
109      Pragma_Simple_Storage_Pool_Type     => True,
110      Pragma_SPARK_Mode                   => True,
111      Pragma_Storage_Size                 => True,
112      Pragma_Suppress                     => True,
113      Pragma_Suppress_Debug_Info          => True,
114      Pragma_Suppress_Initialization      => True,
115      Pragma_Test_Case                    => True,
116      Pragma_Thread_Local_Storage         => True,
117      Pragma_Type_Invariant               => True,
118      Pragma_Unchecked_Union              => True,
119      Pragma_Universal_Aliasing           => True,
120      Pragma_Unmodified                   => True,
121      Pragma_Unreferenced                 => True,
122      Pragma_Unreferenced_Objects         => True,
123      Pragma_Unsuppress                   => True,
124      Pragma_Volatile                     => True,
125      Pragma_Volatile_Components          => True,
126      Pragma_Volatile_Full_Access         => True,
127      Pragma_Warnings                     => True,
128      others                              => False);
129
130   --  The following table lists all pragmas that act as an assertion
131   --  expression.
132
133   Assertion_Expression_Pragma : constant array (Pragma_Id) of Boolean :=
134     (Pragma_Assert                    => True,
135      Pragma_Assert_And_Cut            => True,
136      Pragma_Assume                    => True,
137      Pragma_Check                     => True,
138      Pragma_Contract_Cases            => True,
139      Pragma_Default_Initial_Condition => True,
140      Pragma_Initial_Condition         => True,
141      Pragma_Invariant                 => True,
142      Pragma_Loop_Invariant            => True,
143      Pragma_Loop_Variant              => True,
144      Pragma_Post                      => True,
145      Pragma_Post_Class                => True,
146      Pragma_Postcondition             => True,
147      Pragma_Pre                       => True,
148      Pragma_Pre_Class                 => True,
149      Pragma_Precondition              => True,
150      Pragma_Predicate                 => True,
151      Pragma_Refined_Post              => True,
152      Pragma_Test_Case                 => True,
153      Pragma_Type_Invariant            => True,
154      Pragma_Type_Invariant_Class      => True,
155      others                           => False);
156
157   --  The following table lists all the implementation-defined pragmas that
158   --  should apply to the anonymous object produced by the analysis of a
159   --  single protected or task type. The table should be synchronized with
160   --  Aspect_On_Anonymous_Object_OK in unit Aspects.
161
162   Pragma_On_Anonymous_Object_OK : constant array (Pragma_Id) of Boolean :=
163     (Pragma_Depends => True,
164      Pragma_Global  => True,
165      Pragma_Part_Of => True,
166      others         => False);
167
168   --  The following table lists all the implementation-defined pragmas that
169   --  may apply to a body stub (no language defined pragmas apply). The table
170   --  should be synchronized with Aspect_On_Body_Or_Stub_OK in unit Aspects.
171
172   Pragma_On_Body_Or_Stub_OK : constant array (Pragma_Id) of Boolean :=
173     (Pragma_Refined_Depends => True,
174      Pragma_Refined_Global  => True,
175      Pragma_Refined_Post    => True,
176      Pragma_SPARK_Mode      => True,
177      Pragma_Warnings        => True,
178      others                 => False);
179
180   --  The following table lists all pragmas which are significant in SPARK and
181   --  as a result get translated into verification conditions. The table is an
182   --  amalgamation of the pragmas listed in SPARK RM 16.1 and internally added
183   --  entries.
184
185   Pragma_Significant_In_SPARK : constant array (Pragma_Id) of Boolean :=
186     (Pragma_All_Calls_Remote              => False,
187      Pragma_Asynchronous                  => False,
188      Pragma_Default_Storage_Pool          => False,
189      Pragma_Discard_Names                 => False,
190      Pragma_Dispatching_Domain            => False,
191      Pragma_Priority_Specific_Dispatching => False,
192      Pragma_Remote_Call_Interface         => False,
193      Pragma_Remote_Types                  => False,
194      Pragma_Shared_Passive                => False,
195      Pragma_Task_Dispatching_Policy       => False,
196      Pragma_Unmodified                    => False,
197      Pragma_Unreferenced                  => False,
198      Pragma_Warnings                      => False,
199      others                               => True);
200
201   -----------------
202   -- Subprograms --
203   -----------------
204
205   procedure Analyze_Pragma (N : Node_Id);
206   --  Analyze procedure for pragma reference node N
207
208   procedure Analyze_Contract_Cases_In_Decl_Part
209     (N         : Node_Id;
210      Freeze_Id : Entity_Id := Empty);
211   --  Perform full analysis of delayed pragma Contract_Cases. Freeze_Id is the
212   --  entity of [generic] package body or [generic] subprogram body which
213   --  caused "freezing" of the related contract where the pragma resides.
214
215   procedure Analyze_Depends_In_Decl_Part (N : Node_Id);
216   --  Perform full analysis of delayed pragma Depends. This routine is also
217   --  capable of performing basic analysis of pragma Refined_Depends.
218
219   procedure Analyze_External_Property_In_Decl_Part
220     (N        : Node_Id;
221      Expr_Val : out Boolean);
222   --  Perform full analysis of delayed pragmas Async_Readers, Async_Writers,
223   --  Effective_Reads, Effective_Writes and No_Caching. Flag Expr_Val contains
224   --  the Boolean argument of the pragma or a default True if no argument
225   --  is present.
226
227   procedure Analyze_Global_In_Decl_Part (N : Node_Id);
228   --  Perform full analysis of delayed pragma Global. This routine is also
229   --  capable of performing basic analysis of pragma Refined_Global.
230
231   procedure Analyze_Initial_Condition_In_Decl_Part (N : Node_Id);
232   --  Perform full analysis of delayed pragma Initial_Condition
233
234   procedure Analyze_Initializes_In_Decl_Part (N : Node_Id);
235   --  Perform full analysis of delayed pragma Initializes
236
237   procedure Analyze_Part_Of_In_Decl_Part
238     (N         : Node_Id;
239      Freeze_Id : Entity_Id := Empty);
240   --  Perform full analysis of delayed pragma Part_Of. Freeze_Id is the entity
241   --  of [generic] package body or [generic] subprogram body which caused the
242   --  "freezing" of the related contract where the pragma resides.
243
244   procedure Analyze_Pre_Post_Condition_In_Decl_Part
245     (N         : Node_Id;
246      Freeze_Id : Entity_Id := Empty);
247   --  Perform full analysis of pragmas Precondition and Postcondition.
248   --  Freeze_Id denotes the entity of [generic] package body or [generic]
249   --  subprogram body which caused "freezing" of the related contract where
250   --  the pragma resides.
251
252   procedure Analyze_Refined_Depends_In_Decl_Part (N : Node_Id);
253   --  Preform full analysis of delayed pragma Refined_Depends. This routine
254   --  uses Analyze_Depends_In_Decl_Part as a starting point, then performs
255   --  various consistency checks between Depends and Refined_Depends.
256
257   procedure Analyze_Refined_Global_In_Decl_Part (N : Node_Id);
258   --  Perform full analysis of delayed pragma Refined_Global. This routine
259   --  uses Analyze_Global_In_Decl_Part as a starting point, then performs
260   --  various consistency checks between Global and Refined_Global.
261
262   procedure Analyze_Refined_State_In_Decl_Part
263     (N         : Node_Id;
264      Freeze_Id : Entity_Id := Empty);
265   --  Perform full analysis of delayed pragma Refined_State. Freeze_Id denotes
266   --  the entity of [generic] package body or [generic] subprogram body which
267   --  caused "freezing" of the related contract where the pragma resides.
268
269   procedure Analyze_Subprogram_Variant_In_Decl_Part
270     (N         : Node_Id;
271      Freeze_Id : Entity_Id := Empty);
272   --  Perform full analysis of delayed pragma Subprogram_Variant. Freeze_Id is
273   --  the entity of [generic] package body or [generic] subprogram body which
274   --  caused "freezing" of the related contract where the pragma resides.
275
276   procedure Analyze_Test_Case_In_Decl_Part (N : Node_Id);
277   --  Perform preanalysis of pragma Test_Case
278
279   function Build_Pragma_Check_Equivalent
280     (Prag           : Node_Id;
281      Subp_Id        : Entity_Id := Empty;
282      Inher_Id       : Entity_Id := Empty;
283      Keep_Pragma_Id : Boolean := False) return Node_Id;
284   --  Transform a pre- or [refined] postcondition denoted by Prag into an
285   --  equivalent pragma Check. When the pre- or postcondition is inherited,
286   --  the routine replaces the references of all formals of Inher_Id
287   --  and primitive operations of its controlling type by references
288   --  to the corresponding entities of Subp_Id and the descendant type.
289   --  Keep_Pragma_Id is True when the newly created pragma should be
290   --  in fact of the same kind as the source pragma Prag. This is used
291   --  in GNATprove_Mode to generate the inherited pre- and postconditions.
292
293   procedure Check_Applicable_Policy (N : Node_Id);
294   --  N is either an N_Aspect or an N_Pragma node. There are two cases. If
295   --  the name of the aspect or pragma is not one of those recognized as
296   --  an assertion kind by an Assertion_Policy pragma, then the call has
297   --  no effect. Note that in the case of a pragma derived from an aspect,
298   --  the name we use for the purpose of this procedure is the aspect name,
299   --  which may be different from the pragma name (e.g. Precondition for
300   --  Pre aspect). In addition, 'Class aspects are recognized (and the
301   --  corresponding special names used in the processing).
302   --
303   --  If the name is a valid assertion kind name, then the Check_Policy pragma
304   --  chain is checked for a matching entry (or for an Assertion entry which
305   --  matches all possibilities). If a matching entry is found then the policy
306   --  is checked. If it is On or Check, then the Is_Checked flag is set in
307   --  the aspect or pragma node. If it is Off, Ignore, or Disable, then the
308   --  Is_Ignored flag is set in the aspect or pragma node. Additionally for
309   --  policy Disable, the Is_Disabled flag is set.
310   --
311   --  If no matching Check_Policy pragma is found then the effect depends on
312   --  whether -gnata was used, if so, then the call has no effect, otherwise
313   --  Is_Ignored (but not Is_Disabled) is set True.
314
315   procedure Check_External_Properties
316     (Item : Node_Id;
317      AR   : Boolean;
318      AW   : Boolean;
319      ER   : Boolean;
320      EW   : Boolean);
321   --  Flags AR, AW, ER and EW denote the static values of external properties
322   --  Async_Readers, Async_Writers, Effective_Reads and Effective_Writes. Item
323   --  is the related variable or state. Ensure legality of the combination and
324   --  issue an error for an illegal combination.
325
326   function Check_Kind (Nam : Name_Id) return Name_Id;
327   --  This function is used in connection with pragmas Assert, Check,
328   --  and assertion aspects and pragmas, to determine if Check pragmas
329   --  (or corresponding assertion aspects or pragmas) are currently active
330   --  as determined by the presence of -gnata on the command line (which
331   --  sets the default), and the appearance of pragmas Check_Policy and
332   --  Assertion_Policy as configuration pragmas either in a configuration
333   --  pragma file, or at the start of the current unit, or locally given
334   --  Check_Policy and Assertion_Policy pragmas that are currently active.
335   --
336   --  The value returned is one of the names Check, Ignore, Disable (On
337   --  returns Check, and Off returns Ignore).
338   --
339   --  Note: for assertion kinds Pre'Class, Post'Class, Invariant'Class,
340   --  and Type_Invariant'Class, the name passed is Name_uPre, Name_uPost,
341   --  Name_uInvariant, or Name_uType_Invariant, which corresponds to _Pre,
342   --  _Post, _Invariant, or _Type_Invariant, which are special names used
343   --  in identifiers to represent these attribute references.
344
345   procedure Check_Missing_Part_Of (Item_Id : Entity_Id);
346   --  Determine whether the placement within the state space of an abstract
347   --  state, variable or package instantiation denoted by Item_Id requires the
348   --  use of indicator/option Part_Of. If this is the case, emit an error.
349
350   procedure Collect_Inherited_Class_Wide_Conditions (Subp : Entity_Id);
351   --  In GNATprove mode, when analyzing an overriding subprogram, check
352   --  whether the overridden operations have class-wide pre/postconditions,
353   --  and generate the corresponding pragmas. The pragmas are inserted after
354   --  the subprogram declaration, together with those generated for other
355   --  aspects of the subprogram.
356
357   procedure Collect_Subprogram_Inputs_Outputs
358     (Subp_Id      : Entity_Id;
359      Synthesize   : Boolean := False;
360      Subp_Inputs  : in out Elist_Id;
361      Subp_Outputs : in out Elist_Id;
362      Global_Seen  : out Boolean);
363   --  Subsidiary to the analysis of pragmas Depends, Global, Refined_Depends
364   --  and Refined_Global. Collect all inputs and outputs of subprogram Subp_Id
365   --  in lists Subp_Inputs (inputs) and Subp_Outputs (outputs). The inputs and
366   --  outputs are gathered from:
367   --    1) The formal parameters of the subprogram
368   --    2) The generic formal parameters of the generic subprogram
369   --    3) The current instance of a concurrent type
370   --    4) The items of pragma [Refined_]Global
371   --         or
372   --    5) The items of pragma [Refined_]Depends if there is no pragma
373   --       [Refined_]Global present and flag Synthesize is set to True.
374   --  If the subprogram has no inputs and/or outputs, then the returned list
375   --  is No_Elist. Flag Global_Seen is set when the related subprogram has
376   --  pragma [Refined_]Global.
377
378   function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean;
379   --  N is a pragma appearing in a configuration pragma file. Most such
380   --  pragmas are analyzed when the file is read, before parsing and analyzing
381   --  the main unit. However, the analysis of certain pragmas results in
382   --  adding information to the compiled main unit, and this cannot be done
383   --  till the main unit is processed. Such pragmas return True from this
384   --  function and in Frontend pragmas where Delay_Config_Pragma_Analyze is
385   --  True have their analysis delayed until after the main program is parsed
386   --  and analyzed.
387
388   function Find_Related_Package_Or_Body
389     (Prag      : Node_Id;
390      Do_Checks : Boolean := False) return Node_Id;
391   --  Subsidiary to the analysis of pragmas
392   --    Abstract_State
393   --    Initial_Condition
394   --    Initializes
395   --    Refined_State
396   --  Find the declaration of the related package [body] subject to pragma
397   --  Prag. The return value is either N_Package_Declaration, N_Package_Body,
398   --  or Empty if the placement of the pragma is illegal. If flag Do_Checks is
399   --  set, the routine reports duplicate pragmas.
400
401   function Find_Related_Declaration_Or_Body
402     (Prag      : Node_Id;
403      Do_Checks : Boolean := False) return Node_Id;
404   --  Subsidiary to the analysis of pragmas
405   --    Contract_Cases
406   --    Depends
407   --    Extensions_Visible
408   --    Global
409   --    Initializes
410   --    Max_Entry_Queue_Depth
411   --    Max_Entry_Queue_Length
412   --    Max_Queue_Length
413   --    Post
414   --    Post_Class
415   --    Postcondition
416   --    Pre
417   --    Pre_Class
418   --    Precondition
419   --    Refined_Depends
420   --    Refined_Global
421   --    Refined_Post
422   --    Refined_State
423   --    Test_Case
424   --    Volatile_Function
425   --  as well as attributes 'Old and 'Result. Find the declaration of the
426   --  related entry, subprogram or task type [body] subject to pragma Prag.
427   --  If flag Do_Checks is set, the routine reports duplicate pragmas and
428   --  detects improper use of refinement pragmas in stand alone expression
429   --  functions.
430
431   function Get_Argument
432     (Prag       : Node_Id;
433      Context_Id : Entity_Id := Empty) return Node_Id;
434   --  Obtain the argument of pragma Prag depending on context and the nature
435   --  of the pragma. The argument is extracted in the following manner:
436   --
437   --    When the pragma is generated from an aspect, return the corresponding
438   --    aspect when Context_Id denotes a generic unit.
439   --
440   --    Otherwise return the first argument of Prag
441   --
442   --  Context denotes the entity of the function, package or procedure where
443   --  Prag resides.
444
445   function Get_SPARK_Mode_From_Annotation
446     (N : Node_Id) return SPARK_Mode_Type;
447   --  Given an aspect or pragma SPARK_Mode node, return corresponding mode id
448
449   procedure Initialize;
450   --  Initializes data structures used for pragma processing. Must be called
451   --  before analyzing each new main source program.
452
453   function Is_Config_Static_String (Arg : Node_Id) return Boolean;
454   --  This is called for a configuration pragma that requires either string
455   --  literal or a concatenation of string literals. We cannot use normal
456   --  static string processing because it is too early in the case of the
457   --  pragma appearing in a configuration pragmas file. If Arg is of an
458   --  appropriate form, then this call obtains the string (doing any necessary
459   --  concatenations) and places it in Name_Buffer, setting Name_Len to its
460   --  length, and then returns True. If it is not of the correct form, then an
461   --  appropriate error message is posted, and False is returned.
462
463   function Is_Elaboration_SPARK_Mode (N : Node_Id) return Boolean;
464   --  Determine whether pragma SPARK_Mode appears in the statement part of a
465   --  package body.
466
467   function Is_Enabled_Pragma (Prag : Node_Id) return Boolean;
468   --  Determine whether a Boolean-like SPARK pragma Prag is enabled. To be
469   --  considered enabled, the pragma must either:
470   --    * Appear without its Boolean expression
471   --    * The Boolean expression evaluates to "True"
472   --
473   --  Boolean-like SPARK pragmas differ from pure Boolean Ada pragmas in that
474   --  their optional Boolean expression must be static and cannot benefit from
475   --  forward references. The following are Boolean-like SPARK pragmas:
476   --    Async_Readers
477   --    Async_Writers
478   --    Constant_After_Elaboration
479   --    Effective_Reads
480   --    Effective_Writes
481   --    Extensions_Visible
482   --    Volatile_Function
483
484   function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean;
485   --  The node N is a node for an entity and the issue is whether the
486   --  occurrence is a reference for the purposes of giving warnings about
487   --  unreferenced variables. This function returns True if the reference is
488   --  not a reference from this point of view (e.g. the occurrence in a pragma
489   --  Pack) and False if it is a real reference (e.g. the occurrence in a
490   --  pragma Export);
491
492   function Is_Pragma_String_Literal (Par : Node_Id) return Boolean;
493   --  Given an N_Pragma_Argument_Association node, Par, which has the form of
494   --  an operator symbol, determines whether or not it should be treated as an
495   --  string literal. This is called by Sem_Ch6.Analyze_Operator_Symbol. If
496   --  True is returned, the argument is converted to a string literal. If
497   --  False is returned, then the argument is treated as an entity reference
498   --  to the operator.
499
500   function Is_Private_SPARK_Mode (N : Node_Id) return Boolean;
501   --  Determine whether pragma SPARK_Mode appears in the private part of a
502   --  package.
503
504   function Is_Valid_Assertion_Kind (Nam : Name_Id) return Boolean;
505   --  Returns True if Nam is one of the names recognized as a valid assertion
506   --  kind by the Assertion_Policy pragma. Note that the 'Class cases are
507   --  represented by the corresponding special names Name_uPre, Name_uPost,
508   --  Name_uInvariant, and Name_uType_Invariant (_Pre, _Post, _Invariant,
509   --  and _Type_Invariant).
510
511   procedure Process_Compilation_Unit_Pragmas (N : Node_Id);
512   --  Called at the start of processing compilation unit N to deal with any
513   --  special issues regarding pragmas. In particular, we have to deal with
514   --  Suppress_All at this stage, since it can appear after the unit instead
515   --  of before (actually we allow it to appear anywhere).
516
517   procedure Relocate_Pragmas_To_Anonymous_Object
518     (Typ_Decl : Node_Id;
519      Obj_Decl : Node_Id);
520   --  Relocate all pragmas that appear in the visible declarations of task or
521   --  protected type declaration Typ_Decl after the declaration of anonymous
522   --  object Obj_Decl. Table Pragmas_On_Anonymous_Object_OK contains the list
523   --  of candidate pragmas.
524
525   procedure Relocate_Pragmas_To_Body
526     (Subp_Body   : Node_Id;
527      Target_Body : Node_Id := Empty);
528   --  Resocate all pragmas that follow and apply to subprogram body Subp_Body
529   --  to its own declaration list. Candidate pragmas are classified in table
530   --  Pragma_On_Body_Or_Stub_OK. If Target_Body is set, the pragma are moved
531   --  to the declarations of Target_Body. This formal should be set when
532   --  dealing with subprogram body stubs or expression functions.
533
534   procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id);
535   --  This routine is used to set an encoded interface name. The node S is
536   --  an N_String_Literal node for the external name to be set, and E is an
537   --  entity whose Interface_Name field is to be set. In the normal case where
538   --  S contains a name that is a valid C identifier, then S is simply set as
539   --  the value of the Interface_Name. Otherwise it is encoded as needed by
540   --  particular operating systems. See the body for details of the encoding.
541
542   procedure Set_Overflow_Mode (N : Node_Id);
543   --  Sets Sem.Scope_Suppress according to the overflow modes specified in
544   --  the pragma Overflow_Mode passed in argument. This should only be called
545   --  after N has been successfully analyzed.
546
547   function Test_Case_Arg
548     (Prag        : Node_Id;
549      Arg_Nam     : Name_Id;
550      From_Aspect : Boolean := False) return Node_Id;
551   --  Obtain argument "Name", "Mode", "Ensures" or "Requires" from Test_Case
552   --  pragma Prag as denoted by Arg_Nam. When From_Aspect is set, an attempt
553   --  is made to retrieve the argument from the corresponding aspect if there
554   --  is one. The returned argument has several formats:
555   --
556   --    N_Pragma_Argument_Association if retrieved directly from the pragma
557   --
558   --    N_Component_Association if retrieved from the corresponding aspect and
559   --    the argument appears in a named association form.
560   --
561   --    An arbitrary expression if retrieved from the corresponding aspect and
562   --    the argument appears in positional form.
563   --
564   --    Empty if there is no such argument
565
566   procedure Validate_Compile_Time_Warning_Errors;
567   --  This routine is called after calling the back end to validate pragmas
568   --  Compile_Time_Error and Compile_Time_Warning for size and alignment
569   --  appropriateness. The reason it is called that late is to take advantage
570   --  of any back-annotation of size and alignment performed by the back end.
571
572end Sem_Prag;
573