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-2015, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
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_Default_Initial_Condition    => True,
53      Pragma_Default_Storage_Pool         => True,
54      Pragma_Depends                      => True,
55      Pragma_Discard_Names                => True,
56      Pragma_Dispatching_Domain           => True,
57      Pragma_Effective_Reads              => True,
58      Pragma_Effective_Writes             => True,
59      Pragma_Elaborate_Body               => True,
60      Pragma_Export                       => True,
61      Pragma_Extensions_Visible           => True,
62      Pragma_Favor_Top_Level              => True,
63      Pragma_Ghost                        => True,
64      Pragma_Global                       => True,
65      Pragma_Import                       => True,
66      Pragma_Independent                  => True,
67      Pragma_Independent_Components       => True,
68      Pragma_Initial_Condition            => True,
69      Pragma_Initializes                  => True,
70      Pragma_Inline                       => True,
71      Pragma_Inline_Always                => True,
72      Pragma_Interrupt_Handler            => True,
73      Pragma_Interrupt_Priority           => True,
74      Pragma_Invariant                    => True,
75      Pragma_Linker_Section               => True,
76      Pragma_Lock_Free                    => True,
77      Pragma_No_Elaboration_Code_All      => True,
78      Pragma_No_Return                    => True,
79      Pragma_Obsolescent                  => True,
80      Pragma_Pack                         => True,
81      Pragma_Part_Of                      => True,
82      Pragma_Persistent_BSS               => True,
83      Pragma_Post                         => True,
84      Pragma_Post_Class                   => True,
85      Pragma_Postcondition                => True,
86      Pragma_Pre                          => True,
87      Pragma_Pre_Class                    => True,
88      Pragma_Precondition                 => True,
89      Pragma_Predicate                    => True,
90      Pragma_Preelaborable_Initialization => True,
91      Pragma_Preelaborate                 => True,
92      Pragma_Priority                     => True,
93      Pragma_Pure                         => True,
94      Pragma_Pure_Function                => True,
95      Pragma_Refined_Depends              => True,
96      Pragma_Refined_Global               => True,
97      Pragma_Refined_Post                 => True,
98      Pragma_Refined_State                => True,
99      Pragma_Relative_Deadline            => True,
100      Pragma_Remote_Access_Type           => True,
101      Pragma_Remote_Call_Interface        => True,
102      Pragma_Remote_Types                 => True,
103      Pragma_Shared                       => True,
104      Pragma_Shared_Passive               => True,
105      Pragma_Simple_Storage_Pool_Type     => True,
106      Pragma_SPARK_Mode                   => True,
107      Pragma_Storage_Size                 => True,
108      Pragma_Suppress                     => True,
109      Pragma_Suppress_Debug_Info          => True,
110      Pragma_Suppress_Initialization      => True,
111      Pragma_Test_Case                    => True,
112      Pragma_Thread_Local_Storage         => True,
113      Pragma_Type_Invariant               => True,
114      Pragma_Unchecked_Union              => True,
115      Pragma_Universal_Aliasing           => True,
116      Pragma_Universal_Data               => True,
117      Pragma_Unmodified                   => True,
118      Pragma_Unreferenced                 => True,
119      Pragma_Unreferenced_Objects         => True,
120      Pragma_Unsuppress                   => True,
121      Pragma_Volatile                     => True,
122      Pragma_Volatile_Components          => True,
123      Pragma_Volatile_Full_Access         => True,
124      Pragma_Warnings                     => True,
125      others                              => False);
126
127   --  The following table lists all pragmas that act as an assertion
128   --  expression.
129
130   Assertion_Expression_Pragma : constant array (Pragma_Id) of Boolean :=
131     (Pragma_Assert                    => True,
132      Pragma_Assert_And_Cut            => True,
133      Pragma_Assume                    => True,
134      Pragma_Check                     => True,
135      Pragma_Contract_Cases            => True,
136      Pragma_Default_Initial_Condition => True,
137      Pragma_Initial_Condition         => True,
138      Pragma_Invariant                 => True,
139      Pragma_Loop_Invariant            => True,
140      Pragma_Loop_Variant              => True,
141      Pragma_Post                      => True,
142      Pragma_Post_Class                => True,
143      Pragma_Postcondition             => True,
144      Pragma_Pre                       => True,
145      Pragma_Pre_Class                 => True,
146      Pragma_Precondition              => True,
147      Pragma_Predicate                 => True,
148      Pragma_Refined_Post              => True,
149      Pragma_Test_Case                 => True,
150      Pragma_Type_Invariant            => True,
151      Pragma_Type_Invariant_Class      => True,
152      others                           => False);
153
154   --  The following table lists all the implementation-defined pragmas that
155   --  should apply to the anonymous object produced by the analysis of a
156   --  single protected or task type. The table should be synchronized with
157   --  Aspect_On_Anonymous_Object_OK in unit Aspects.
158
159   Pragma_On_Anonymous_Object_OK : constant array (Pragma_Id) of Boolean :=
160     (Pragma_Depends => True,
161      Pragma_Global  => True,
162      Pragma_Part_Of => True,
163      others         => False);
164
165   --  The following table lists all the implementation-defined pragmas that
166   --  may apply to a body stub (no language defined pragmas apply). The table
167   --  should be synchronized with Aspect_On_Body_Or_Stub_OK in unit Aspects.
168
169   Pragma_On_Body_Or_Stub_OK : constant array (Pragma_Id) of Boolean :=
170     (Pragma_Refined_Depends => True,
171      Pragma_Refined_Global  => True,
172      Pragma_Refined_Post    => True,
173      Pragma_SPARK_Mode      => True,
174      Pragma_Warnings        => True,
175      others                 => False);
176
177   -----------------
178   -- Subprograms --
179   -----------------
180
181   procedure Analyze_Pragma (N : Node_Id);
182   --  Analyze procedure for pragma reference node N
183
184   procedure Analyze_Contract_Cases_In_Decl_Part
185     (N         : Node_Id;
186      Freeze_Id : Entity_Id := Empty);
187   --  Perform full analysis of delayed pragma Contract_Cases. Freeze_Id is the
188   --  entity of [generic] package body or [generic] subprogram body which
189   --  caused "freezing" of the related contract where the pragma resides.
190
191   procedure Analyze_Depends_In_Decl_Part (N : Node_Id);
192   --  Perform full analysis of delayed pragma Depends. This routine is also
193   --  capable of performing basic analysis of pragma Refined_Depends.
194
195   procedure Analyze_External_Property_In_Decl_Part
196     (N        : Node_Id;
197      Expr_Val : out Boolean);
198   --  Perform full analysis of delayed pragmas Async_Readers, Async_Writers,
199   --  Effective_Reads and Effective_Writes. Flag Expr_Val contains the Boolean
200   --  argument of the pragma or a default True if no argument is present.
201
202   procedure Analyze_Global_In_Decl_Part (N : Node_Id);
203   --  Perform full analysis of delayed pragma Global. This routine is also
204   --  capable of performing basic analysis of pragma Refind_Global.
205
206   procedure Analyze_Initial_Condition_In_Decl_Part (N : Node_Id);
207   --  Perform full analysis of delayed pragma Initial_Condition
208
209   procedure Analyze_Initializes_In_Decl_Part (N : Node_Id);
210   --  Perform full analysis of delayed pragma Initializes
211
212   procedure Analyze_Part_Of_In_Decl_Part
213     (N         : Node_Id;
214      Freeze_Id : Entity_Id := Empty);
215   --  Perform full analysis of delayed pragma Part_Of. Freeze_Id is the entity
216   --  of [generic] package body or [generic] subprogram body which caused the
217   --  "freezing" of the related contract where the pragma resides.
218
219   procedure Analyze_Pre_Post_Condition_In_Decl_Part
220     (N         : Node_Id;
221      Freeze_Id : Entity_Id := Empty);
222   --  Perform full analysis of pragmas Precondition and Postcondition.
223   --  Freeze_Id denotes the entity of [generic] package body or [generic]
224   --  subprogram body which caused "freezing" of the related contract where
225   --  the pragma resides.
226
227   procedure Analyze_Refined_Depends_In_Decl_Part (N : Node_Id);
228   --  Preform full analysis of delayed pragma Refined_Depends. This routine
229   --  uses Analyze_Depends_In_Decl_Part as a starting point, then performs
230   --  various consistency checks between Depends and Refined_Depends.
231
232   procedure Analyze_Refined_Global_In_Decl_Part (N : Node_Id);
233   --  Perform full analysis of delayed pragma Refined_Global. This routine
234   --  uses Analyze_Global_In_Decl_Part as a starting point, then performs
235   --  various consistency checks between Global and Refined_Global.
236
237   procedure Analyze_Refined_State_In_Decl_Part
238     (N         : Node_Id;
239      Freeze_Id : Entity_Id := Empty);
240   --  Perform full analysis of delayed pragma Refined_State. Freeze_Id denotes
241   --  the entity of [generic] package body or [generic] subprogram body which
242   --  caused "freezing" of the related contract where the pragma resides.
243
244   procedure Analyze_Test_Case_In_Decl_Part (N : Node_Id);
245   --  Perform preanalysis of pragma Test_Case
246
247   procedure Check_Applicable_Policy (N : Node_Id);
248   --  N is either an N_Aspect or an N_Pragma node. There are two cases. If
249   --  the name of the aspect or pragma is not one of those recognized as
250   --  an assertion kind by an Assertion_Policy pragma, then the call has
251   --  no effect. Note that in the case of a pragma derived from an aspect,
252   --  the name we use for the purpose of this procedure is the aspect name,
253   --  which may be different from the pragma name (e.g. Precondition for
254   --  Pre aspect). In addition, 'Class aspects are recognized (and the
255   --  corresponding special names used in the processing).
256   --
257   --  If the name is a valid assertion kind name, then the Check_Policy pragma
258   --  chain is checked for a matching entry (or for an Assertion entry which
259   --  matches all possibilities). If a matching entry is found then the policy
260   --  is checked. If it is On or Check, then the Is_Checked flag is set in
261   --  the aspect or pragma node. If it is Off, Ignore, or Disable, then the
262   --  Is_Ignored flag is set in the aspect or pragma node. Additionally for
263   --  policy Disable, the Is_Disabled flag is set.
264   --
265   --  If no matching Check_Policy pragma is found then the effect depends on
266   --  whether -gnata was used, if so, then the call has no effect, otherwise
267   --  Is_Ignored (but not Is_Disabled) is set True.
268
269   procedure Check_External_Properties
270     (Item : Node_Id;
271      AR   : Boolean;
272      AW   : Boolean;
273      ER   : Boolean;
274      EW   : Boolean);
275   --  Flags AR, AW, ER and EW denote the static values of external properties
276   --  Async_Readers, Async_Writers, Effective_Reads and Effective_Writes. Item
277   --  is the related variable or state. Ensure legality of the combination and
278   --  issue an error for an illegal combination.
279
280   function Check_Kind (Nam : Name_Id) return Name_Id;
281   --  This function is used in connection with pragmas Assert, Check,
282   --  and assertion aspects and pragmas, to determine if Check pragmas
283   --  (or corresponding assertion aspects or pragmas) are currently active
284   --  as determined by the presence of -gnata on the command line (which
285   --  sets the default), and the appearance of pragmas Check_Policy and
286   --  Assertion_Policy as configuration pragmas either in a configuration
287   --  pragma file, or at the start of the current unit, or locally given
288   --  Check_Policy and Assertion_Policy pragmas that are currently active.
289   --
290   --  The value returned is one of the names Check, Ignore, Disable (On
291   --  returns Check, and Off returns Ignore).
292   --
293   --  Note: for assertion kinds Pre'Class, Post'Class, Invariant'Class,
294   --  and Type_Invariant'Class, the name passed is Name_uPre, Name_uPost,
295   --  Name_uInvariant, or Name_uType_Invariant, which corresponds to _Pre,
296   --  _Post, _Invariant, or _Type_Invariant, which are special names used
297   --  in identifiers to represent these attribute references.
298
299   procedure Check_Missing_Part_Of (Item_Id : Entity_Id);
300   --  Determine whether the placement within the state space of an abstract
301   --  state, variable or package instantiation denoted by Item_Id requires the
302   --  use of indicator/option Part_Of. If this is the case, emit an error.
303
304   procedure Collect_Subprogram_Inputs_Outputs
305     (Subp_Id      : Entity_Id;
306      Synthesize   : Boolean := False;
307      Subp_Inputs  : in out Elist_Id;
308      Subp_Outputs : in out Elist_Id;
309      Global_Seen  : out Boolean);
310   --  Subsidiary to the analysis of pragmas Depends, Global, Refined_Depends
311   --  and Refined_Global. The routine is also used by GNATprove. Collect all
312   --  inputs and outputs of subprogram Subp_Id in lists Subp_Inputs (inputs)
313   --  and Subp_Outputs (outputs). The inputs and outputs are gathered from:
314   --    1) The formal parameters of the subprogram
315   --    2) The generic formal parameters of the generic subprogram
316   --    3) The current instance of a concurrent type
317   --    4) The items of pragma [Refined_]Global
318   --         or
319   --    5) The items of pragma [Refined_]Depends if there is no pragma
320   --       [Refined_]Global present and flag Synthesize is set to True.
321   --  If the subprogram has no inputs and/or outputs, then the returned list
322   --  is No_Elist. Flag Global_Seen is set when the related subprogram has
323   --  pragma [Refined_]Global.
324
325   function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean;
326   --  N is a pragma appearing in a configuration pragma file. Most such
327   --  pragmas are analyzed when the file is read, before parsing and analyzing
328   --  the main unit. However, the analysis of certain pragmas results in
329   --  adding information to the compiled main unit, and this cannot be done
330   --  till the main unit is processed. Such pragmas return True from this
331   --  function and in Frontend pragmas where Delay_Config_Pragma_Analyze is
332   --  True have their analysis delayed until after the main program is parsed
333   --  and analyzed.
334
335   function Find_Related_Package_Or_Body
336     (Prag      : Node_Id;
337      Do_Checks : Boolean := False) return Node_Id;
338   --  Subsidiary to the analysis of pragmas Abstract_State, Initial_Condition,
339   --  Initializes and Refined_State. Find the declaration of the related
340   --  package [body] subject to pragma Prag. The return value is either
341   --  N_Package_Declaration, N_Package_Body or Empty if the placement of
342   --  the pragma is illegal. If flag Do_Checks is set, the routine reports
343   --  duplicate pragmas.
344
345   function Find_Related_Declaration_Or_Body
346     (Prag      : Node_Id;
347      Do_Checks : Boolean := False) return Node_Id;
348   --  Subsidiary to the analysis of pragmas
349   --    Contract_Cases
350   --    Depends
351   --    Extensions_Visible
352   --    Global
353   --    Post
354   --    Post_Class
355   --    Postcondition
356   --    Pre
357   --    Pre_Class
358   --    Precondition
359   --    Refined_Depends
360   --    Refined_Global
361   --    Refined_Post
362   --    Test_Case
363   --  as well as attributes 'Old and 'Result. Find the declaration of the
364   --  related entry, subprogram or task type [body] subject to pragma Prag.
365   --  If flag Do_Checks is set, the routine reports duplicate pragmas and
366   --  detects improper use of refinement pragmas in stand alone expression
367   --  functions.
368
369   function Get_Argument
370     (Prag       : Node_Id;
371      Context_Id : Node_Id := Empty) return Node_Id;
372   --  Obtain the argument of pragma Prag depending on context and the nature
373   --  of the pragma. The argument is extracted in the following manner:
374   --
375   --    When the pragma is generated from an aspect, return the corresponding
376   --    aspect for ASIS or when Context_Id denotes a generic unit.
377   --
378   --    Otherwise return the first argument of Prag
379   --
380   --  Context denotes the entity of the function, package or procedure where
381   --  Prag resides.
382
383   function Get_SPARK_Mode_From_Pragma (N : Node_Id) return SPARK_Mode_Type;
384   --  Given a pragma SPARK_Mode node, return corresponding mode id
385
386   procedure Initialize;
387   --  Initializes data structures used for pragma processing. Must be called
388   --  before analyzing each new main source program.
389
390   function Is_Config_Static_String (Arg : Node_Id) return Boolean;
391   --  This is called for a configuration pragma that requires either string
392   --  literal or a concatenation of string literals. We cannot use normal
393   --  static string processing because it is too early in the case of the
394   --  pragma appearing in a configuration pragmas file. If Arg is of an
395   --  appropriate form, then this call obtains the string (doing any necessary
396   --  concatenations) and places it in Name_Buffer, setting Name_Len to its
397   --  length, and then returns True. If it is not of the correct form, then an
398   --  appropriate error message is posted, and False is returned.
399
400   function Is_Elaboration_SPARK_Mode (N : Node_Id) return Boolean;
401   --  Determine whether pragma SPARK_Mode appears in the statement part of a
402   --  package body.
403
404   function Is_Enabled_Pragma (Prag : Node_Id) return Boolean;
405   --  Determine whether a Boolean-like SPARK pragma Prag is enabled. To be
406   --  considered enabled, the pragma must either:
407   --    * Appear without its Boolean expression
408   --    * The Boolean expression evaluates to "True"
409   --
410   --  Boolean-like SPARK pragmas differ from pure Boolean Ada pragmas in that
411   --  their optional Boolean expression must be static and cannot benefit from
412   --  forward references. The following are Boolean-like SPARK pragmas:
413   --    Async_Readers
414   --    Async_Writers
415   --    Constant_After_Elaboration
416   --    Effective_Reads
417   --    Effective_Writes
418   --    Extensions_Visible
419   --    Volatile_Function
420
421   function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean;
422   --  The node N is a node for an entity and the issue is whether the
423   --  occurrence is a reference for the purposes of giving warnings about
424   --  unreferenced variables. This function returns True if the reference is
425   --  not a reference from this point of view (e.g. the occurrence in a pragma
426   --  Pack) and False if it is a real reference (e.g. the occurrence in a
427   --  pragma Export);
428
429   function Is_Pragma_String_Literal (Par : Node_Id) return Boolean;
430   --  Given an N_Pragma_Argument_Association node, Par, which has the form of
431   --  an operator symbol, determines whether or not it should be treated as an
432   --  string literal. This is called by Sem_Ch6.Analyze_Operator_Symbol. If
433   --  True is returned, the argument is converted to a string literal. If
434   --  False is returned, then the argument is treated as an entity reference
435   --  to the operator.
436
437   function Is_Private_SPARK_Mode (N : Node_Id) return Boolean;
438   --  Determine whether pragma SPARK_Mode appears in the private part of a
439   --  package.
440
441   function Is_Valid_Assertion_Kind (Nam : Name_Id) return Boolean;
442   --  Returns True if Nam is one of the names recognized as a valid assertion
443   --  kind by the Assertion_Policy pragma. Note that the 'Class cases are
444   --  represented by the corresponding special names Name_uPre, Name_uPost,
445   --  Name_uInvariant, and Name_uType_Invariant (_Pre, _Post, _Invariant,
446   --  and _Type_Invariant).
447
448   procedure Process_Compilation_Unit_Pragmas (N : Node_Id);
449   --  Called at the start of processing compilation unit N to deal with any
450   --  special issues regarding pragmas. In particular, we have to deal with
451   --  Suppress_All at this stage, since it can appear after the unit instead
452   --  of before (actually we allow it to appear anywhere).
453
454   procedure Relocate_Pragmas_To_Anonymous_Object
455     (Typ_Decl : Node_Id;
456      Obj_Decl : Node_Id);
457   --  Relocate all pragmas that appear in the visible declarations of task or
458   --  protected type declaration Typ_Decl after the declaration of anonymous
459   --  object Obj_Decl. Table Pragmas_On_Anonymous_Object_OK contains the list
460   --  of candidate pragmas.
461
462   procedure Relocate_Pragmas_To_Body
463     (Subp_Body   : Node_Id;
464      Target_Body : Node_Id := Empty);
465   --  Resocate all pragmas that follow and apply to subprogram body Subp_Body
466   --  to its own declaration list. Candidate pragmas are classified in table
467   --  Pragma_On_Body_Or_Stub_OK. If Target_Body is set, the pragma are moved
468   --  to the declarations of Target_Body. This formal should be set when
469   --  dealing with subprogram body stubs or expression functions.
470
471   procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id);
472   --  This routine is used to set an encoded interface name. The node S is
473   --  an N_String_Literal node for the external name to be set, and E is an
474   --  entity whose Interface_Name field is to be set. In the normal case where
475   --  S contains a name that is a valid C identifier, then S is simply set as
476   --  the value of the Interface_Name. Otherwise it is encoded as needed by
477   --  particular operating systems. See the body for details of the encoding.
478
479   function Test_Case_Arg
480     (Prag        : Node_Id;
481      Arg_Nam     : Name_Id;
482      From_Aspect : Boolean := False) return Node_Id;
483   --  Obtain argument "Name", "Mode", "Ensures" or "Requires" from Test_Case
484   --  pragma Prag as denoted by Arg_Nam. When From_Aspect is set, an attempt
485   --  is made to retrieve the argument from the corresponding aspect if there
486   --  is one. The returned argument has several formats:
487   --
488   --    N_Pragma_Argument_Association if retrieved directly from the pragma
489   --
490   --    N_Component_Association if retrieved from the corresponding aspect and
491   --    the argument appears in a named association form.
492   --
493   --    An arbitrary expression if retrieved from the corresponding aspect and
494   --    the argument appears in positional form.
495   --
496   --    Empty if there is no such argument
497
498end Sem_Prag;
499