1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                              S E M _ C H 6                               --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2013, 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
26with Types; use Types;
27package Sem_Ch6 is
28
29   type Conformance_Type is
30     (Type_Conformant, Mode_Conformant, Subtype_Conformant, Fully_Conformant);
31   pragma Ordered (Conformance_Type);
32   --  Conformance type used in conformance checks between specs and bodies,
33   --  and for overriding. The literals match the RM definitions of the
34   --  corresponding terms. This is an ordered type, since each conformance
35   --  type is stronger than the ones preceding it.
36
37   procedure Analyze_Abstract_Subprogram_Declaration (N : Node_Id);
38   procedure Analyze_Expression_Function             (N : Node_Id);
39   procedure Analyze_Extended_Return_Statement       (N : Node_Id);
40   procedure Analyze_Function_Call                   (N : Node_Id);
41   procedure Analyze_Operator_Symbol                 (N : Node_Id);
42   procedure Analyze_Parameter_Association           (N : Node_Id);
43   procedure Analyze_Procedure_Call                  (N : Node_Id);
44   procedure Analyze_Simple_Return_Statement         (N : Node_Id);
45   procedure Analyze_Subprogram_Declaration          (N : Node_Id);
46   procedure Analyze_Subprogram_Body                 (N : Node_Id);
47
48   procedure Analyze_Subprogram_Body_Contract (Body_Id : Entity_Id);
49   --  Analyze all delayed aspects chained on the contract of subprogram body
50   --  Body_Id as if they appeared at the end of a declarative region. The
51   --  aspects in question are:
52   --    Refined_Depends
53   --    Refined_Global
54
55   procedure Analyze_Subprogram_Contract (Subp : Entity_Id);
56   --  Analyze all delayed aspects chained on the contract of subprogram Subp
57   --  as if they appeared at the end of a declarative region. The aspects in
58   --  question are:
59   --    Contract_Cases
60   --    Postcondition
61   --    Precondition
62   --    Test_Case
63
64   function Analyze_Subprogram_Specification (N : Node_Id) return Entity_Id;
65   --  Analyze subprogram specification in both subprogram declarations
66   --  and body declarations. Returns the defining entity for the
67   --  specification N.
68
69   procedure Cannot_Inline
70     (Msg        : String;
71      N          : Node_Id;
72      Subp       : Entity_Id;
73      Is_Serious : Boolean := False);
74   --  This procedure is called if the node N, an instance of a call to
75   --  subprogram Subp, cannot be inlined. Msg is the message to be issued,
76   --  which ends with ? (it does not end with ?p?, this routine takes care of
77   --  the need to change ? to ?p?). Temporarily the behavior of this routine
78   --  depends on the value of -gnatd.k:
79   --
80   --    * If -gnatd.k is not set (ie. old inlining model) then if Subp has
81   --      a pragma Always_Inlined, then an error message is issued (by
82   --      removing the last character of Msg). If Subp is not Always_Inlined,
83   --      then a warning is issued if the flag Ineffective_Inline_Warnings
84   --      is set, adding ?p to the msg, and if not, the call has no effect.
85   --
86   --    * If -gnatd.k is set (ie. new inlining model) then:
87   --      - If Is_Serious is true, then an error is reported (by removing the
88   --        last character of Msg);
89   --
90   --      - otherwise:
91   --
92   --        * Compiling without optimizations if Subp has a pragma
93   --          Always_Inlined, then an error message is issued; if Subp is
94   --          not Always_Inlined, then a warning is issued if the flag
95   --          Ineffective_Inline_Warnings is set (adding p?), and if not,
96   --          the call has no effect.
97   --
98   --        * Compiling with optimizations then a warning is issued if the
99   --          flag Ineffective_Inline_Warnings is set (adding p?); otherwise
100   --          no effect since inlining may be performed by the backend.
101
102   procedure Check_Conventions (Typ : Entity_Id);
103   --  Ada 2005 (AI-430): Check that the conventions of all inherited and
104   --  overridden dispatching operations of type Typ are consistent with their
105   --  respective counterparts.
106
107   procedure Check_Delayed_Subprogram (Designator : Entity_Id);
108   --  Designator can be a E_Subprogram_Type, E_Procedure or E_Function. If a
109   --  type in its profile depends on a private type without a full
110   --  declaration, indicate that the subprogram or type is delayed.
111
112   procedure Check_Discriminant_Conformance
113     (N        : Node_Id;
114      Prev     : Entity_Id;
115      Prev_Loc : Node_Id);
116   --  Check that the discriminants of a full type N fully conform to the
117   --  discriminants of the corresponding partial view Prev. Prev_Loc indicates
118   --  the source location of the partial view, which may be different than
119   --  Prev in the case of private types.
120
121   procedure Check_Fully_Conformant
122     (New_Id  : Entity_Id;
123      Old_Id  : Entity_Id;
124      Err_Loc : Node_Id := Empty);
125   --  Check that two callable entities (subprograms, entries, literals)
126   --  are fully conformant, post error message if not (RM 6.3.1(17)) with
127   --  the flag being placed on the Err_Loc node if it is specified, and
128   --  on the appropriate component of the New_Id construct if not. Note:
129   --  when checking spec/body conformance, New_Id must be the body entity
130   --  and Old_Id is the spec entity (the code in the implementation relies
131   --  on this ordering, and in any case, this makes sense, since if flags
132   --  are to be placed on the construct, they clearly belong on the body.
133
134   procedure Check_Mode_Conformant
135     (New_Id   : Entity_Id;
136      Old_Id   : Entity_Id;
137      Err_Loc  : Node_Id := Empty;
138      Get_Inst : Boolean := False);
139   --  Check that two callable entities (subprograms, entries, literals)
140   --  are mode conformant, post error message if not (RM 6.3.1(15)) with
141   --  the flag being placed on the Err_Loc node if it is specified, and
142   --  on the appropriate component of the New_Id construct if not. The
143   --  argument Get_Inst is set to True when this is a check against a
144   --  formal access-to-subprogram type, indicating that mapping of types
145   --  is needed.
146
147   procedure Check_Overriding_Indicator
148     (Subp            : Entity_Id;
149      Overridden_Subp : Entity_Id;
150      Is_Primitive    : Boolean);
151   --  Verify the consistency of an overriding_indicator given for subprogram
152   --  declaration, body, renaming, or instantiation.  Overridden_Subp is set
153   --  if the scope where we are introducing the subprogram contains a
154   --  type-conformant subprogram that becomes hidden by the new subprogram.
155   --  Is_Primitive indicates whether the subprogram is primitive.
156
157   procedure Check_Subtype_Conformant
158     (New_Id                   : Entity_Id;
159      Old_Id                   : Entity_Id;
160      Err_Loc                  : Node_Id := Empty;
161      Skip_Controlling_Formals : Boolean := False;
162      Get_Inst                 : Boolean := False);
163   --  Check that two callable entities (subprograms, entries, literals)
164   --  are subtype conformant, post error message if not (RM 6.3.1(16)),
165   --  the flag being placed on the Err_Loc node if it is specified, and
166   --  on the appropriate component of the New_Id construct if not.
167   --  Skip_Controlling_Formals is True when checking the conformance of
168   --  a subprogram that implements an interface operation. In that case,
169   --  only the non-controlling formals can (and must) be examined. The
170   --  argument Get_Inst is set to True when this is a check against a
171   --  formal access-to-subprogram type, indicating that mapping of types
172   --  is needed.
173
174   procedure Check_Type_Conformant
175     (New_Id  : Entity_Id;
176      Old_Id  : Entity_Id;
177      Err_Loc : Node_Id := Empty);
178   --  Check that two callable entities (subprograms, entries, literals)
179   --  are type conformant, post error message if not (RM 6.3.1(14)) with
180   --  the flag being placed on the Err_Loc node if it is specified, and
181   --  on the appropriate component of the New_Id construct if not.
182
183   function Conforming_Types
184     (T1       : Entity_Id;
185      T2       : Entity_Id;
186      Ctype    : Conformance_Type;
187      Get_Inst : Boolean := False) return Boolean;
188   --  Check that the types of two formal parameters are conforming. In most
189   --  cases this is just a name comparison, but within an instance it involves
190   --  generic actual types, and in the presence of anonymous access types
191   --  it must examine the designated types. The argument Get_Inst is set to
192   --  True when this is a check against a formal access-to-subprogram type,
193   --  indicating that mapping of types is needed.
194
195   procedure Create_Extra_Formals (E : Entity_Id);
196   --  For each parameter of a subprogram or entry that requires an additional
197   --  formal (such as for access parameters and indefinite discriminated
198   --  parameters), creates the appropriate formal and attach it to its
199   --  associated parameter. Each extra formal will also be appended to
200   --  the end of Subp's parameter list (with each subsequent extra formal
201   --  being attached to the preceding extra formal).
202
203   function Find_Corresponding_Spec
204     (N          : Node_Id;
205      Post_Error : Boolean := True) return Entity_Id;
206   --  Use the subprogram specification in the body to retrieve the previous
207   --  subprogram declaration, if any.
208
209   function Fully_Conformant (New_Id, Old_Id : Entity_Id) return Boolean;
210   --  Determine whether two callable entities (subprograms, entries,
211   --  literals) are fully conformant (RM 6.3.1(17))
212
213   function Fully_Conformant_Expressions
214     (Given_E1 : Node_Id;
215      Given_E2 : Node_Id) return Boolean;
216   --  Determines if two (non-empty) expressions are fully conformant
217   --  as defined by (RM 6.3.1(18-21))
218
219   function Fully_Conformant_Discrete_Subtypes
220      (Given_S1 : Node_Id;
221       Given_S2 : Node_Id) return Boolean;
222   --  Determines if two subtype definitions are fully conformant. Used
223   --  for entry family conformance checks (RM 6.3.1 (24)).
224
225   procedure Install_Entity (E : Entity_Id);
226   --  Place a single entity on the visibility chain
227
228   procedure Install_Formals (Id : Entity_Id);
229   --  On entry to a subprogram body, make the formals visible. Note that
230   --  simply placing the subprogram on the scope stack is not sufficient:
231   --  the formals must become the current entities for their names. This
232   --  procedure is also used to get visibility to the formals when analyzing
233   --  preconditions and postconditions appearing in the spec.
234
235   function Is_Interface_Conformant
236     (Tagged_Type : Entity_Id;
237      Iface_Prim  : Entity_Id;
238      Prim        : Entity_Id) return Boolean;
239   --  Returns true if both primitives have a matching name (including support
240   --  for names of inherited private primitives --which have suffix 'P'), they
241   --  are type conformant, and Prim is defined in the scope of Tagged_Type.
242   --  Special management is done for functions returning interfaces.
243
244   procedure List_Inherited_Pre_Post_Aspects (E : Entity_Id);
245   --  E is the entity for a subprogram or generic subprogram spec. This call
246   --  lists all inherited Pre/Post aspects if List_Inherited_Pre_Post is True.
247
248   procedure May_Need_Actuals (Fun : Entity_Id);
249   --  Flag functions that can be called without parameters, i.e. those that
250   --  have no parameters, or those for which defaults exist for all parameters
251   --  Used for subprogram declarations and for access subprogram declarations,
252   --  where they apply to the anonymous designated type. On return the flag
253   --  Set_Needs_No_Actuals is set appropriately in Fun.
254
255   function Mode_Conformant (New_Id, Old_Id : Entity_Id) return Boolean;
256   --  Determine whether two callable entities (subprograms, entries,
257   --  literals) are mode conformant (RM 6.3.1(15))
258
259   procedure New_Overloaded_Entity
260     (S            : Entity_Id;
261      Derived_Type : Entity_Id := Empty);
262   --  Process new overloaded entity. Overloaded entities are created by
263   --  enumeration type declarations, subprogram specifications, entry
264   --  declarations, and (implicitly) by type derivations. If Derived_Type
265   --  is non-empty then this is a subprogram derived for that type.
266
267   procedure Process_Formals (T : List_Id; Related_Nod : Node_Id);
268   --  Enter the formals in the scope of the subprogram or entry, and
269   --  analyze default expressions if any. The implicit types created for
270   --  access parameter are attached to the Related_Nod which comes from the
271   --  context.
272
273   procedure Reference_Body_Formals (Spec : Entity_Id; Bod : Entity_Id);
274   --  If there is a separate spec for a subprogram or generic subprogram, the
275   --  formals of the body are treated as references to the corresponding
276   --  formals of the spec. This reference does not count as an actual use of
277   --  the formal, in order to diagnose formals that are unused in the body.
278   --  This procedure is also used in renaming_as_body declarations, where
279   --  the formals of the specification must be treated as body formals that
280   --  correspond to the previous subprogram declaration, and not as new
281   --  entities with their defining entry in the cross-reference information.
282
283   procedure Set_Actual_Subtypes (N : Node_Id; Subp : Entity_Id);
284   --  If the formals of a subprogram are unconstrained, build a subtype
285   --  declaration that uses the bounds or discriminants of the actual to
286   --  construct an actual subtype for them. This is an optimization that
287   --  is done only in some cases where the actual subtype cannot change
288   --  during execution of the subprogram. By setting the actual subtype
289   --  once, we avoid recomputing it unnecessarily.
290
291   procedure Set_Formal_Mode (Formal_Id : Entity_Id);
292   --  Set proper Ekind to reflect formal mode (in, out, in out)
293
294   function Subtype_Conformant
295     (New_Id                   : Entity_Id;
296      Old_Id                   : Entity_Id;
297      Skip_Controlling_Formals : Boolean := False) return Boolean;
298   --  Determine whether two callable entities (subprograms, entries, literals)
299   --  are subtype conformant (RM 6.3.1(16)). Skip_Controlling_Formals is True
300   --  when checking the conformance of a subprogram that implements an
301   --  interface operation. In that case, only the non-controlling formals
302   --  can (and must) be examined.
303
304   function Type_Conformant
305     (New_Id                   : Entity_Id;
306      Old_Id                   : Entity_Id;
307      Skip_Controlling_Formals : Boolean := False) return Boolean;
308   --  Determine whether two callable entities (subprograms, entries, literals)
309   --  are type conformant (RM 6.3.1(14)). Skip_Controlling_Formals is True
310   --  when checking the conformance of a subprogram that implements an
311   --  interface operation. In that case, only the non-controlling formals
312   --  can (and must) be examined.
313
314   procedure Valid_Operator_Definition (Designator : Entity_Id);
315   --  Verify that an operator definition has the proper number of formals
316
317end Sem_Ch6;
318