1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2014, 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 Checks
; use Checks
;
29 with Einfo
; use Einfo
;
30 with Elists
; use Elists
;
31 with Exp_Atag
; use Exp_Atag
;
32 with Exp_Ch2
; use Exp_Ch2
;
33 with Exp_Ch3
; use Exp_Ch3
;
34 with Exp_Ch6
; use Exp_Ch6
;
35 with Exp_Ch9
; use Exp_Ch9
;
36 with Exp_Dist
; use Exp_Dist
;
37 with Exp_Imgv
; use Exp_Imgv
;
38 with Exp_Pakd
; use Exp_Pakd
;
39 with Exp_Strm
; use Exp_Strm
;
40 with Exp_Tss
; use Exp_Tss
;
41 with Exp_Util
; use Exp_Util
;
42 with Fname
; use Fname
;
43 with Freeze
; use Freeze
;
44 with Gnatvsn
; use Gnatvsn
;
45 with Itypes
; use Itypes
;
47 with Namet
; use Namet
;
48 with Nmake
; use Nmake
;
49 with Nlists
; use Nlists
;
51 with Restrict
; use Restrict
;
52 with Rident
; use Rident
;
53 with Rtsfind
; use Rtsfind
;
55 with Sem_Aux
; use Sem_Aux
;
56 with Sem_Ch6
; use Sem_Ch6
;
57 with Sem_Ch7
; use Sem_Ch7
;
58 with Sem_Ch8
; use Sem_Ch8
;
59 with Sem_Eval
; use Sem_Eval
;
60 with Sem_Res
; use Sem_Res
;
61 with Sem_Util
; use Sem_Util
;
62 with Sinfo
; use Sinfo
;
63 with Snames
; use Snames
;
64 with Stand
; use Stand
;
65 with Stringt
; use Stringt
;
66 with Targparm
; use Targparm
;
67 with Tbuild
; use Tbuild
;
68 with Ttypes
; use Ttypes
;
69 with Uintp
; use Uintp
;
70 with Uname
; use Uname
;
71 with Validsw
; use Validsw
;
73 package body Exp_Attr
is
75 -----------------------
76 -- Local Subprograms --
77 -----------------------
79 function Build_Array_VS_Func
81 Nod
: Node_Id
) return Entity_Id
;
82 -- Build function to test Valid_Scalars for array type A_Type. Nod is the
83 -- Valid_Scalars attribute node, used to insert the function body, and the
84 -- value returned is the entity of the constructed function body. We do not
85 -- bother to generate a separate spec for this subprogram.
87 function Build_Record_VS_Func
89 Nod
: Node_Id
) return Entity_Id
;
90 -- Build function to test Valid_Scalars for record type A_Type. Nod is the
91 -- Valid_Scalars attribute node, used to insert the function body, and the
92 -- value returned is the entity of the constructed function body. We do not
93 -- bother to generate a separate spec for this subprogram.
95 procedure Compile_Stream_Body_In_Scope
100 -- The body for a stream subprogram may be generated outside of the scope
101 -- of the type. If the type is fully private, it may depend on the full
102 -- view of other types (e.g. indexes) that are currently private as well.
103 -- We install the declarations of the package in which the type is declared
104 -- before compiling the body in what is its proper environment. The Check
105 -- parameter indicates if checks are to be suppressed for the stream body.
106 -- We suppress checks for array/record reads, since the rule is that these
107 -- are like assignments, out of range values due to uninitialized storage,
108 -- or other invalid values do NOT cause a Constraint_Error to be raised.
109 -- If we are within an instance body all visibility has been established
110 -- already and there is no need to install the package.
112 procedure Expand_Access_To_Protected_Op
116 -- An attribute reference to a protected subprogram is transformed into
117 -- a pair of pointers: one to the object, and one to the operations.
118 -- This expansion is performed for 'Access and for 'Unrestricted_Access.
120 procedure Expand_Fpt_Attribute
125 -- This procedure expands a call to a floating-point attribute function.
126 -- N is the attribute reference node, and Args is a list of arguments to
127 -- be passed to the function call. Pkg identifies the package containing
128 -- the appropriate instantiation of System.Fat_Gen. Float arguments in Args
129 -- have already been converted to the floating-point type for which Pkg was
130 -- instantiated. The Nam argument is the relevant attribute processing
131 -- routine to be called. This is the same as the attribute name, except in
132 -- the Unaligned_Valid case.
134 procedure Expand_Fpt_Attribute_R
(N
: Node_Id
);
135 -- This procedure expands a call to a floating-point attribute function
136 -- that takes a single floating-point argument. The function to be called
137 -- is always the same as the attribute name.
139 procedure Expand_Fpt_Attribute_RI
(N
: Node_Id
);
140 -- This procedure expands a call to a floating-point attribute function
141 -- that takes one floating-point argument and one integer argument. The
142 -- function to be called is always the same as the attribute name.
144 procedure Expand_Fpt_Attribute_RR
(N
: Node_Id
);
145 -- This procedure expands a call to a floating-point attribute function
146 -- that takes two floating-point arguments. The function to be called
147 -- is always the same as the attribute name.
149 procedure Expand_Loop_Entry_Attribute
(N
: Node_Id
);
150 -- Handle the expansion of attribute 'Loop_Entry. As a result, the related
151 -- loop may be converted into a conditional block. See body for details.
153 procedure Expand_Min_Max_Attribute
(N
: Node_Id
);
154 -- Handle the expansion of attributes 'Max and 'Min, including expanding
155 -- then out if we are in Modify_Tree_For_C mode.
157 procedure Expand_Pred_Succ_Attribute
(N
: Node_Id
);
158 -- Handles expansion of Pred or Succ attributes for case of non-real
159 -- operand with overflow checking required.
161 procedure Expand_Update_Attribute
(N
: Node_Id
);
162 -- Handle the expansion of attribute Update
164 function Get_Index_Subtype
(N
: Node_Id
) return Entity_Id
;
165 -- Used for Last, Last, and Length, when the prefix is an array type.
166 -- Obtains the corresponding index subtype.
168 procedure Find_Fat_Info
170 Fat_Type
: out Entity_Id
;
171 Fat_Pkg
: out RE_Id
);
172 -- Given a floating-point type T, identifies the package containing the
173 -- attributes for this type (returned in Fat_Pkg), and the corresponding
174 -- type for which this package was instantiated from Fat_Gen. Error if T
175 -- is not a floating-point type.
177 function Find_Stream_Subprogram
179 Nam
: TSS_Name_Type
) return Entity_Id
;
180 -- Returns the stream-oriented subprogram attribute for Typ. For tagged
181 -- types, the corresponding primitive operation is looked up, else the
182 -- appropriate TSS from the type itself, or from its closest ancestor
183 -- defining it, is returned. In both cases, inheritance of representation
184 -- aspects is thus taken into account.
186 function Full_Base
(T
: Entity_Id
) return Entity_Id
;
187 -- The stream functions need to examine the underlying representation of
188 -- composite types. In some cases T may be non-private but its base type
189 -- is, in which case the function returns the corresponding full view.
191 function Get_Stream_Convert_Pragma
(T
: Entity_Id
) return Node_Id
;
192 -- Given a type, find a corresponding stream convert pragma that applies to
193 -- the implementation base type of this type (Typ). If found, return the
194 -- pragma node, otherwise return Empty if no pragma is found.
196 function Is_Constrained_Packed_Array
(Typ
: Entity_Id
) return Boolean;
197 -- Utility for array attributes, returns true on packed constrained
198 -- arrays, and on access to same.
200 function Is_Inline_Floating_Point_Attribute
(N
: Node_Id
) return Boolean;
201 -- Returns true iff the given node refers to an attribute call that
202 -- can be expanded directly by the back end and does not need front end
203 -- expansion. Typically used for rounding and truncation attributes that
204 -- appear directly inside a conversion to integer.
206 -------------------------
207 -- Build_Array_VS_Func --
208 -------------------------
210 function Build_Array_VS_Func
212 Nod
: Node_Id
) return Entity_Id
214 Loc
: constant Source_Ptr
:= Sloc
(Nod
);
215 Func_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
216 Comp_Type
: constant Entity_Id
:= Component_Type
(A_Type
);
217 Body_Stmts
: List_Id
;
218 Index_List
: List_Id
;
221 function Test_Component
return List_Id
;
222 -- Create one statement to test validity of one component designated by
223 -- a full set of indexes. Returns statement list containing test.
225 function Test_One_Dimension
(N
: Int
) return List_Id
;
226 -- Create loop to test one dimension of the array. The single statement
227 -- in the loop body tests the inner dimensions if any, or else the
228 -- single component. Note that this procedure is called recursively,
229 -- with N being the dimension to be initialized. A call with N greater
230 -- than the number of dimensions simply generates the component test,
231 -- terminating the recursion. Returns statement list containing tests.
237 function Test_Component
return List_Id
is
243 Make_Indexed_Component
(Loc
,
244 Prefix
=> Make_Identifier
(Loc
, Name_uA
),
245 Expressions
=> Index_List
);
247 if Is_Scalar_Type
(Comp_Type
) then
250 Anam
:= Name_Valid_Scalars
;
254 Make_If_Statement
(Loc
,
258 Make_Attribute_Reference
(Loc
,
259 Attribute_Name
=> Anam
,
261 Then_Statements
=> New_List
(
262 Make_Simple_Return_Statement
(Loc
,
263 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
)))));
266 ------------------------
267 -- Test_One_Dimension --
268 ------------------------
270 function Test_One_Dimension
(N
: Int
) return List_Id
is
274 -- If all dimensions dealt with, we simply test the component
276 if N
> Number_Dimensions
(A_Type
) then
277 return Test_Component
;
279 -- Here we generate the required loop
283 Make_Defining_Identifier
(Loc
, New_External_Name
('J', N
));
285 Append
(New_Occurrence_Of
(Index
, Loc
), Index_List
);
288 Make_Implicit_Loop_Statement
(Nod
,
291 Make_Iteration_Scheme
(Loc
,
292 Loop_Parameter_Specification
=>
293 Make_Loop_Parameter_Specification
(Loc
,
294 Defining_Identifier
=> Index
,
295 Discrete_Subtype_Definition
=>
296 Make_Attribute_Reference
(Loc
,
297 Prefix
=> Make_Identifier
(Loc
, Name_uA
),
298 Attribute_Name
=> Name_Range
,
299 Expressions
=> New_List
(
300 Make_Integer_Literal
(Loc
, N
))))),
301 Statements
=> Test_One_Dimension
(N
+ 1)),
302 Make_Simple_Return_Statement
(Loc
,
303 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
305 end Test_One_Dimension
;
307 -- Start of processing for Build_Array_VS_Func
310 Index_List
:= New_List
;
311 Body_Stmts
:= Test_One_Dimension
(1);
313 -- Parameter is always (A : A_Typ)
315 Formals
:= New_List
(
316 Make_Parameter_Specification
(Loc
,
317 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_uA
),
319 Out_Present
=> False,
320 Parameter_Type
=> New_Occurrence_Of
(A_Type
, Loc
)));
324 Set_Ekind
(Func_Id
, E_Function
);
325 Set_Is_Internal
(Func_Id
);
328 Make_Subprogram_Body
(Loc
,
330 Make_Function_Specification
(Loc
,
331 Defining_Unit_Name
=> Func_Id
,
332 Parameter_Specifications
=> Formals
,
334 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
335 Declarations
=> New_List
,
336 Handled_Statement_Sequence
=>
337 Make_Handled_Sequence_Of_Statements
(Loc
,
338 Statements
=> Body_Stmts
)));
340 if not Debug_Generated_Code
then
341 Set_Debug_Info_Off
(Func_Id
);
344 Set_Is_Pure
(Func_Id
);
346 end Build_Array_VS_Func
;
348 --------------------------
349 -- Build_Record_VS_Func --
350 --------------------------
354 -- function _Valid_Scalars (X : T) return Boolean is
356 -- -- Check discriminants
358 -- if not X.D1'Valid_Scalars or else
359 -- not X.D2'Valid_Scalars or else
365 -- -- Check components
367 -- if not X.C1'Valid_Scalars or else
368 -- not X.C2'Valid_Scalars or else
374 -- -- Check variant part
378 -- if not X.C2'Valid_Scalars or else
379 -- not X.C3'Valid_Scalars or else
386 -- if not X.Cn'Valid_Scalars or else
394 -- end _Valid_Scalars;
396 function Build_Record_VS_Func
398 Nod
: Node_Id
) return Entity_Id
400 Loc
: constant Source_Ptr
:= Sloc
(R_Type
);
401 Func_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
402 X
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_X
);
404 function Make_VS_Case
407 Discrs
: Elist_Id
:= New_Elmt_List
) return List_Id
;
408 -- Building block for variant valid scalars. Given a Component_List node
409 -- CL, it generates an 'if' followed by a 'case' statement that compares
410 -- all components of local temporaries named X and Y (that are declared
411 -- as formals at some upper level). E provides the Sloc to be used for
412 -- the generated code.
416 L
: List_Id
) return Node_Id
;
417 -- Building block for variant validate scalars. Given the list, L, of
418 -- components (or discriminants) L, it generates a return statement that
419 -- compares all components of local temporaries named X and Y (that are
420 -- declared as formals at some upper level). E provides the Sloc to be
421 -- used for the generated code.
427 -- <Make_VS_If on shared components>
430 -- when V1 => <Make_VS_Case> on subcomponents
432 -- when Vn => <Make_VS_Case> on subcomponents
435 function Make_VS_Case
438 Discrs
: Elist_Id
:= New_Elmt_List
) return List_Id
440 Loc
: constant Source_Ptr
:= Sloc
(E
);
441 Result
: constant List_Id
:= New_List
;
446 Append_To
(Result
, Make_VS_If
(E
, Component_Items
(CL
)));
448 if No
(Variant_Part
(CL
)) then
452 Variant
:= First_Non_Pragma
(Variants
(Variant_Part
(CL
)));
458 Alt_List
:= New_List
;
459 while Present
(Variant
) loop
461 Make_Case_Statement_Alternative
(Loc
,
462 Discrete_Choices
=> New_Copy_List
(Discrete_Choices
(Variant
)),
464 Make_VS_Case
(E
, Component_List
(Variant
), Discrs
)));
465 Next_Non_Pragma
(Variant
);
469 Make_Case_Statement
(Loc
,
471 Make_Selected_Component
(Loc
,
472 Prefix
=> Make_Identifier
(Loc
, Name_X
),
473 Selector_Name
=> New_Copy
(Name
(Variant_Part
(CL
)))),
474 Alternatives
=> Alt_List
));
486 -- not X.C1'Valid_Scalars
488 -- not X.C2'Valid_Scalars
494 -- or a null statement if the list L is empty
498 L
: List_Id
) return Node_Id
500 Loc
: constant Source_Ptr
:= Sloc
(E
);
503 Field_Name
: Name_Id
;
508 return Make_Null_Statement
(Loc
);
513 C
:= First_Non_Pragma
(L
);
514 while Present
(C
) loop
515 Def_Id
:= Defining_Identifier
(C
);
516 Field_Name
:= Chars
(Def_Id
);
518 -- The tags need not be checked since they will always be valid
520 -- Note also that in the following, we use Make_Identifier for
521 -- the component names. Use of New_Occurrence_Of to identify
522 -- the components would be incorrect because wrong entities for
523 -- discriminants could be picked up in the private type case.
525 -- Don't bother with abstract parent in interface case
527 if Field_Name
= Name_uParent
528 and then Is_Interface
(Etype
(Def_Id
))
532 -- Don't bother with tag, always valid, and not scalar anyway
534 elsif Field_Name
= Name_uTag
then
537 -- Don't bother with component with no scalar components
539 elsif not Scalar_Part_Present
(Etype
(Def_Id
)) then
542 -- Normal case, generate Valid_Scalars attribute reference
545 Evolve_Or_Else
(Cond
,
548 Make_Attribute_Reference
(Loc
,
550 Make_Selected_Component
(Loc
,
552 Make_Identifier
(Loc
, Name_X
),
554 Make_Identifier
(Loc
, Field_Name
)),
555 Attribute_Name
=> Name_Valid_Scalars
)));
562 return Make_Null_Statement
(Loc
);
566 Make_Implicit_If_Statement
(E
,
568 Then_Statements
=> New_List
(
569 Make_Simple_Return_Statement
(Loc
,
571 New_Occurrence_Of
(Standard_False
, Loc
))));
576 -- Local Declarations
578 Def
: constant Node_Id
:= Parent
(R_Type
);
579 Comps
: constant Node_Id
:= Component_List
(Type_Definition
(Def
));
580 Stmts
: constant List_Id
:= New_List
;
581 Pspecs
: constant List_Id
:= New_List
;
585 Make_Parameter_Specification
(Loc
,
586 Defining_Identifier
=> X
,
587 Parameter_Type
=> New_Occurrence_Of
(R_Type
, Loc
)));
590 Make_VS_If
(R_Type
, Discriminant_Specifications
(Def
)));
591 Append_List_To
(Stmts
, Make_VS_Case
(R_Type
, Comps
));
594 Make_Simple_Return_Statement
(Loc
,
595 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
598 Make_Subprogram_Body
(Loc
,
600 Make_Function_Specification
(Loc
,
601 Defining_Unit_Name
=> Func_Id
,
602 Parameter_Specifications
=> Pspecs
,
603 Result_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
)),
604 Declarations
=> New_List
,
605 Handled_Statement_Sequence
=>
606 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stmts
)),
607 Suppress
=> Discriminant_Check
);
609 if not Debug_Generated_Code
then
610 Set_Debug_Info_Off
(Func_Id
);
613 Set_Is_Pure
(Func_Id
);
615 end Build_Record_VS_Func
;
617 ----------------------------------
618 -- Compile_Stream_Body_In_Scope --
619 ----------------------------------
621 procedure Compile_Stream_Body_In_Scope
627 Installed
: Boolean := False;
628 Scop
: constant Entity_Id
:= Scope
(Arr
);
629 Curr
: constant Entity_Id
:= Current_Scope
;
633 and then not In_Open_Scopes
(Scop
)
634 and then Ekind
(Scop
) = E_Package
636 -- If we are within an instance body, then all visibility has been
637 -- established already and there is no need to install the package.
639 and then not In_Instance_Body
642 Install_Visible_Declarations
(Scop
);
643 Install_Private_Declarations
(Scop
);
646 -- The entities in the package are now visible, but the generated
647 -- stream entity must appear in the current scope (usually an
648 -- enclosing stream function) so that itypes all have their proper
655 Insert_Action
(N
, Decl
);
657 Insert_Action
(N
, Decl
, Suppress
=> All_Checks
);
662 -- Remove extra copy of current scope, and package itself
665 End_Package_Scope
(Scop
);
667 end Compile_Stream_Body_In_Scope
;
669 -----------------------------------
670 -- Expand_Access_To_Protected_Op --
671 -----------------------------------
673 procedure Expand_Access_To_Protected_Op
678 -- The value of the attribute_reference is a record containing two
679 -- fields: an access to the protected object, and an access to the
680 -- subprogram itself. The prefix is a selected component.
682 Loc
: constant Source_Ptr
:= Sloc
(N
);
684 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
687 E_T
: constant Entity_Id
:= Equivalent_Type
(Btyp
);
688 Acc
: constant Entity_Id
:=
689 Etype
(Next_Component
(First_Component
(E_T
)));
693 function May_Be_External_Call
return Boolean;
694 -- If the 'Access is to a local operation, but appears in a context
695 -- where it may lead to a call from outside the object, we must treat
696 -- this as an external call. Clearly we cannot tell without full
697 -- flow analysis, and a subsequent call that uses this 'Access may
698 -- lead to a bounded error (trying to seize locks twice, e.g.). For
699 -- now we treat 'Access as a potential external call if it is an actual
700 -- in a call to an outside subprogram.
702 --------------------------
703 -- May_Be_External_Call --
704 --------------------------
706 function May_Be_External_Call
return Boolean is
708 Par
: Node_Id
:= Parent
(N
);
711 -- Account for the case where the Access attribute is part of a
712 -- named parameter association.
714 if Nkind
(Par
) = N_Parameter_Association
then
718 if Nkind
(Par
) in N_Subprogram_Call
719 and then Is_Entity_Name
(Name
(Par
))
721 Subp
:= Entity
(Name
(Par
));
722 return not In_Open_Scopes
(Scope
(Subp
));
726 end May_Be_External_Call
;
728 -- Start of processing for Expand_Access_To_Protected_Op
731 -- Within the body of the protected type, the prefix designates a local
732 -- operation, and the object is the first parameter of the corresponding
733 -- protected body of the current enclosing operation.
735 if Is_Entity_Name
(Pref
) then
736 if May_Be_External_Call
then
738 New_Occurrence_Of
(External_Subprogram
(Entity
(Pref
)), Loc
);
742 (Protected_Body_Subprogram
(Entity
(Pref
)), Loc
);
745 -- Don't traverse the scopes when the attribute occurs within an init
746 -- proc, because we directly use the _init formal of the init proc in
749 Curr
:= Current_Scope
;
750 if not Is_Init_Proc
(Curr
) then
751 pragma Assert
(In_Open_Scopes
(Scope
(Entity
(Pref
))));
753 while Scope
(Curr
) /= Scope
(Entity
(Pref
)) loop
754 Curr
:= Scope
(Curr
);
758 -- In case of protected entries the first formal of its Protected_
759 -- Body_Subprogram is the address of the object.
761 if Ekind
(Curr
) = E_Entry
then
765 (Protected_Body_Subprogram
(Curr
)), Loc
);
767 -- If the current scope is an init proc, then use the address of the
768 -- _init formal as the object reference.
770 elsif Is_Init_Proc
(Curr
) then
772 Make_Attribute_Reference
(Loc
,
773 Prefix
=> New_Occurrence_Of
(First_Formal
(Curr
), Loc
),
774 Attribute_Name
=> Name_Address
);
776 -- In case of protected subprograms the first formal of its
777 -- Protected_Body_Subprogram is the object and we get its address.
781 Make_Attribute_Reference
(Loc
,
785 (Protected_Body_Subprogram
(Curr
)), Loc
),
786 Attribute_Name
=> Name_Address
);
789 -- Case where the prefix is not an entity name. Find the
790 -- version of the protected operation to be called from
791 -- outside the protected object.
797 (Entity
(Selector_Name
(Pref
))), Loc
);
800 Make_Attribute_Reference
(Loc
,
801 Prefix
=> Relocate_Node
(Prefix
(Pref
)),
802 Attribute_Name
=> Name_Address
);
806 Make_Attribute_Reference
(Loc
,
808 Attribute_Name
=> Name_Access
);
810 -- We set the type of the access reference to the already generated
811 -- access_to_subprogram type, and declare the reference analyzed, to
812 -- prevent further expansion when the enclosing aggregate is analyzed.
814 Set_Etype
(Sub_Ref
, Acc
);
815 Set_Analyzed
(Sub_Ref
);
819 Expressions
=> New_List
(Obj_Ref
, Sub_Ref
));
821 -- Sub_Ref has been marked as analyzed, but we still need to make sure
822 -- Sub is correctly frozen.
824 Freeze_Before
(N
, Entity
(Sub
));
827 Analyze_And_Resolve
(N
, E_T
);
829 -- For subsequent analysis, the node must retain its type. The backend
830 -- will replace it with the equivalent type where needed.
833 end Expand_Access_To_Protected_Op
;
835 --------------------------
836 -- Expand_Fpt_Attribute --
837 --------------------------
839 procedure Expand_Fpt_Attribute
845 Loc
: constant Source_Ptr
:= Sloc
(N
);
846 Typ
: constant Entity_Id
:= Etype
(N
);
850 -- The function name is the selected component Attr_xxx.yyy where
851 -- Attr_xxx is the package name, and yyy is the argument Nam.
853 -- Note: it would be more usual to have separate RE entries for each
854 -- of the entities in the Fat packages, but first they have identical
855 -- names (so we would have to have lots of renaming declarations to
856 -- meet the normal RE rule of separate names for all runtime entities),
857 -- and second there would be an awful lot of them.
860 Make_Selected_Component
(Loc
,
861 Prefix
=> New_Occurrence_Of
(RTE
(Pkg
), Loc
),
862 Selector_Name
=> Make_Identifier
(Loc
, Nam
));
864 -- The generated call is given the provided set of parameters, and then
865 -- wrapped in a conversion which converts the result to the target type
866 -- We use the base type as the target because a range check may be
870 Unchecked_Convert_To
(Base_Type
(Etype
(N
)),
871 Make_Function_Call
(Loc
,
873 Parameter_Associations
=> Args
)));
875 Analyze_And_Resolve
(N
, Typ
);
876 end Expand_Fpt_Attribute
;
878 ----------------------------
879 -- Expand_Fpt_Attribute_R --
880 ----------------------------
882 -- The single argument is converted to its root type to call the
883 -- appropriate runtime function, with the actual call being built
884 -- by Expand_Fpt_Attribute
886 procedure Expand_Fpt_Attribute_R
(N
: Node_Id
) is
887 E1
: constant Node_Id
:= First
(Expressions
(N
));
891 Find_Fat_Info
(Etype
(E1
), Ftp
, Pkg
);
893 (N
, Pkg
, Attribute_Name
(N
),
894 New_List
(Unchecked_Convert_To
(Ftp
, Relocate_Node
(E1
))));
895 end Expand_Fpt_Attribute_R
;
897 -----------------------------
898 -- Expand_Fpt_Attribute_RI --
899 -----------------------------
901 -- The first argument is converted to its root type and the second
902 -- argument is converted to standard long long integer to call the
903 -- appropriate runtime function, with the actual call being built
904 -- by Expand_Fpt_Attribute
906 procedure Expand_Fpt_Attribute_RI
(N
: Node_Id
) is
907 E1
: constant Node_Id
:= First
(Expressions
(N
));
910 E2
: constant Node_Id
:= Next
(E1
);
912 Find_Fat_Info
(Etype
(E1
), Ftp
, Pkg
);
914 (N
, Pkg
, Attribute_Name
(N
),
916 Unchecked_Convert_To
(Ftp
, Relocate_Node
(E1
)),
917 Unchecked_Convert_To
(Standard_Integer
, Relocate_Node
(E2
))));
918 end Expand_Fpt_Attribute_RI
;
920 -----------------------------
921 -- Expand_Fpt_Attribute_RR --
922 -----------------------------
924 -- The two arguments are converted to their root types to call the
925 -- appropriate runtime function, with the actual call being built
926 -- by Expand_Fpt_Attribute
928 procedure Expand_Fpt_Attribute_RR
(N
: Node_Id
) is
929 E1
: constant Node_Id
:= First
(Expressions
(N
));
930 E2
: constant Node_Id
:= Next
(E1
);
935 Find_Fat_Info
(Etype
(E1
), Ftp
, Pkg
);
937 (N
, Pkg
, Attribute_Name
(N
),
939 Unchecked_Convert_To
(Ftp
, Relocate_Node
(E1
)),
940 Unchecked_Convert_To
(Ftp
, Relocate_Node
(E2
))));
941 end Expand_Fpt_Attribute_RR
;
943 ---------------------------------
944 -- Expand_Loop_Entry_Attribute --
945 ---------------------------------
947 procedure Expand_Loop_Entry_Attribute
(N
: Node_Id
) is
948 procedure Build_Conditional_Block
952 If_Stmt
: out Node_Id
;
953 Blk_Stmt
: out Node_Id
);
954 -- Create a block Blk_Stmt with an empty declarative list and a single
955 -- loop Loop_Stmt. The block is encased in an if statement If_Stmt with
956 -- condition Cond. If_Stmt is Empty when there is no condition provided.
958 function Is_Array_Iteration
(N
: Node_Id
) return Boolean;
959 -- Determine whether loop statement N denotes an Ada 2012 iteration over
962 -----------------------------
963 -- Build_Conditional_Block --
964 -----------------------------
966 procedure Build_Conditional_Block
970 If_Stmt
: out Node_Id
;
971 Blk_Stmt
: out Node_Id
)
974 -- Do not reanalyze the original loop statement because it is simply
977 Set_Analyzed
(Loop_Stmt
);
980 Make_Block_Statement
(Loc
,
981 Declarations
=> New_List
,
982 Handled_Statement_Sequence
=>
983 Make_Handled_Sequence_Of_Statements
(Loc
,
984 Statements
=> New_List
(Loop_Stmt
)));
986 if Present
(Cond
) then
988 Make_If_Statement
(Loc
,
990 Then_Statements
=> New_List
(Blk_Stmt
));
994 end Build_Conditional_Block
;
996 ------------------------
997 -- Is_Array_Iteration --
998 ------------------------
1000 function Is_Array_Iteration
(N
: Node_Id
) return Boolean is
1001 Stmt
: constant Node_Id
:= Original_Node
(N
);
1005 if Nkind
(Stmt
) = N_Loop_Statement
1006 and then Present
(Iteration_Scheme
(Stmt
))
1007 and then Present
(Iterator_Specification
(Iteration_Scheme
(Stmt
)))
1009 Iter
:= Iterator_Specification
(Iteration_Scheme
(Stmt
));
1012 Of_Present
(Iter
) and then Is_Array_Type
(Etype
(Name
(Iter
)));
1016 end Is_Array_Iteration
;
1020 Exprs
: constant List_Id
:= Expressions
(N
);
1021 Pref
: constant Node_Id
:= Prefix
(N
);
1022 Typ
: constant Entity_Id
:= Etype
(Pref
);
1025 Installed
: Boolean;
1027 Loop_Id
: Entity_Id
;
1028 Loop_Stmt
: Node_Id
;
1031 Temp_Decl
: Node_Id
;
1032 Temp_Id
: Entity_Id
;
1034 -- Start of processing for Expand_Loop_Entry_Attribute
1037 -- Step 1: Find the related loop
1039 -- The loop label variant of attribute 'Loop_Entry already has all the
1040 -- information in its expression.
1042 if Present
(Exprs
) then
1043 Loop_Id
:= Entity
(First
(Exprs
));
1044 Loop_Stmt
:= Label_Construct
(Parent
(Loop_Id
));
1046 -- Climb the parent chain to find the nearest enclosing loop. Skip all
1047 -- internally generated loops for quantified expressions.
1051 while Present
(Loop_Stmt
) loop
1052 if Nkind
(Loop_Stmt
) = N_Loop_Statement
1053 and then Present
(Identifier
(Loop_Stmt
))
1058 Loop_Stmt
:= Parent
(Loop_Stmt
);
1061 Loop_Id
:= Entity
(Identifier
(Loop_Stmt
));
1064 Loc
:= Sloc
(Loop_Stmt
);
1066 -- Step 2: Transform the loop
1068 -- The loop has already been transformed during the expansion of a prior
1069 -- 'Loop_Entry attribute. Retrieve the declarative list of the block.
1071 if Has_Loop_Entry_Attributes
(Loop_Id
) then
1073 -- When the related loop name appears as the argument of attribute
1074 -- Loop_Entry, the corresponding label construct is the generated
1075 -- block statement. This is because the expander reuses the label.
1077 if Nkind
(Loop_Stmt
) = N_Block_Statement
then
1078 Decls
:= Declarations
(Loop_Stmt
);
1080 -- In all other cases, the loop must appear in the handled sequence
1081 -- of statements of the generated block.
1085 (Nkind
(Parent
(Loop_Stmt
)) = N_Handled_Sequence_Of_Statements
1087 Nkind
(Parent
(Parent
(Loop_Stmt
))) = N_Block_Statement
);
1089 Decls
:= Declarations
(Parent
(Parent
(Loop_Stmt
)));
1094 -- Transform the loop into a conditional block
1097 Set_Has_Loop_Entry_Attributes
(Loop_Id
);
1098 Scheme
:= Iteration_Scheme
(Loop_Stmt
);
1100 -- Infinite loops are transformed into:
1103 -- Temp1 : constant <type of Pref1> := <Pref1>;
1105 -- TempN : constant <type of PrefN> := <PrefN>;
1108 -- <original source statements with attribute rewrites>
1113 Build_Conditional_Block
(Loc
,
1115 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1121 -- While loops are transformed into:
1123 -- function Fnn return Boolean is
1125 -- <condition actions>
1126 -- return <condition>;
1131 -- Temp1 : constant <type of Pref1> := <Pref1>;
1133 -- TempN : constant <type of PrefN> := <PrefN>;
1136 -- <original source statements with attribute rewrites>
1137 -- exit when not Fnn;
1142 -- Note that loops over iterators and containers are already
1143 -- converted into while loops.
1145 elsif Present
(Condition
(Scheme
)) then
1147 Func_Decl
: Node_Id
;
1148 Func_Id
: Entity_Id
;
1152 -- Wrap the condition of the while loop in a Boolean function.
1153 -- This avoids the duplication of the same code which may lead
1154 -- to gigi issues with respect to multiple declaration of the
1155 -- same entity in the presence of side effects or checks. Note
1156 -- that the condition actions must also be relocated to the
1157 -- wrapping function.
1160 -- <condition actions>
1161 -- return <condition>;
1163 if Present
(Condition_Actions
(Scheme
)) then
1164 Stmts
:= Condition_Actions
(Scheme
);
1170 Make_Simple_Return_Statement
(Loc
,
1171 Expression
=> Relocate_Node
(Condition
(Scheme
))));
1174 -- function Fnn return Boolean is
1179 Func_Id
:= Make_Temporary
(Loc
, 'F');
1181 Make_Subprogram_Body
(Loc
,
1183 Make_Function_Specification
(Loc
,
1184 Defining_Unit_Name
=> Func_Id
,
1185 Result_Definition
=>
1186 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
1187 Declarations
=> Empty_List
,
1188 Handled_Statement_Sequence
=>
1189 Make_Handled_Sequence_Of_Statements
(Loc
,
1190 Statements
=> Stmts
));
1192 -- The function is inserted before the related loop. Make sure
1193 -- to analyze it in the context of the loop's enclosing scope.
1195 Push_Scope
(Scope
(Loop_Id
));
1196 Insert_Action
(Loop_Stmt
, Func_Decl
);
1199 -- Transform the original while loop into an infinite loop
1200 -- where the last statement checks the negated condition. This
1201 -- placement ensures that the condition will not be evaluated
1202 -- twice on the first iteration.
1204 Set_Iteration_Scheme
(Loop_Stmt
, Empty
);
1208 -- exit when not Fnn;
1210 Append_To
(Statements
(Loop_Stmt
),
1211 Make_Exit_Statement
(Loc
,
1215 Make_Function_Call
(Loc
,
1216 Name
=> New_Occurrence_Of
(Func_Id
, Loc
)))));
1218 Build_Conditional_Block
(Loc
,
1220 Make_Function_Call
(Loc
,
1221 Name
=> New_Occurrence_Of
(Func_Id
, Loc
)),
1222 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1227 -- Ada 2012 iteration over an array is transformed into:
1229 -- if <Array_Nam>'Length (1) > 0
1230 -- and then <Array_Nam>'Length (N) > 0
1233 -- Temp1 : constant <type of Pref1> := <Pref1>;
1235 -- TempN : constant <type of PrefN> := <PrefN>;
1237 -- for X in ... loop -- multiple loops depending on dims
1238 -- <original source statements with attribute rewrites>
1243 elsif Is_Array_Iteration
(Loop_Stmt
) then
1245 Array_Nam
: constant Entity_Id
:=
1246 Entity
(Name
(Iterator_Specification
1247 (Iteration_Scheme
(Original_Node
(Loop_Stmt
)))));
1248 Num_Dims
: constant Pos
:=
1249 Number_Dimensions
(Etype
(Array_Nam
));
1250 Cond
: Node_Id
:= Empty
;
1254 -- Generate a check which determines whether all dimensions of
1255 -- the array are non-null.
1257 for Dim
in 1 .. Num_Dims
loop
1261 Make_Attribute_Reference
(Loc
,
1262 Prefix
=> New_Occurrence_Of
(Array_Nam
, Loc
),
1263 Attribute_Name
=> Name_Length
,
1264 Expressions
=> New_List
(
1265 Make_Integer_Literal
(Loc
, Dim
))),
1267 Make_Integer_Literal
(Loc
, 0));
1275 Right_Opnd
=> Check
);
1279 Build_Conditional_Block
(Loc
,
1281 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1286 -- For loops are transformed into:
1288 -- if <Low> <= <High> then
1290 -- Temp1 : constant <type of Pref1> := <Pref1>;
1292 -- TempN : constant <type of PrefN> := <PrefN>;
1294 -- for <Def_Id> in <Low> .. <High> loop
1295 -- <original source statements with attribute rewrites>
1300 elsif Present
(Loop_Parameter_Specification
(Scheme
)) then
1302 Loop_Spec
: constant Node_Id
:=
1303 Loop_Parameter_Specification
(Scheme
);
1308 Subt_Def
:= Discrete_Subtype_Definition
(Loop_Spec
);
1310 -- When the loop iterates over a subtype indication with a
1311 -- range, use the low and high bounds of the subtype itself.
1313 if Nkind
(Subt_Def
) = N_Subtype_Indication
then
1314 Subt_Def
:= Scalar_Range
(Etype
(Subt_Def
));
1317 pragma Assert
(Nkind
(Subt_Def
) = N_Range
);
1324 Left_Opnd
=> New_Copy_Tree
(Low_Bound
(Subt_Def
)),
1325 Right_Opnd
=> New_Copy_Tree
(High_Bound
(Subt_Def
)));
1327 Build_Conditional_Block
(Loc
,
1329 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1335 Decls
:= Declarations
(Blk
);
1338 -- Step 3: Create a constant to capture the value of the prefix at the
1339 -- entry point into the loop.
1342 -- Temp : constant <type of Pref> := <Pref>;
1344 Temp_Id
:= Make_Temporary
(Loc
, 'P');
1347 Make_Object_Declaration
(Loc
,
1348 Defining_Identifier
=> Temp_Id
,
1349 Constant_Present
=> True,
1350 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
1351 Expression
=> Relocate_Node
(Pref
));
1352 Append_To
(Decls
, Temp_Decl
);
1354 -- Step 4: Analyze all bits
1356 Installed
:= Current_Scope
= Scope
(Loop_Id
);
1358 -- Depending on the pracement of attribute 'Loop_Entry relative to the
1359 -- associated loop, ensure the proper visibility for analysis.
1361 if not Installed
then
1362 Push_Scope
(Scope
(Loop_Id
));
1365 -- The analysis of the conditional block takes care of the constant
1368 if Present
(Result
) then
1369 Rewrite
(Loop_Stmt
, Result
);
1370 Analyze
(Loop_Stmt
);
1372 -- The conditional block was analyzed when a previous 'Loop_Entry was
1373 -- expanded. There is no point in reanalyzing the block, simply analyze
1374 -- the declaration of the constant.
1377 Analyze
(Temp_Decl
);
1380 Rewrite
(N
, New_Occurrence_Of
(Temp_Id
, Loc
));
1383 if not Installed
then
1386 end Expand_Loop_Entry_Attribute
;
1388 ------------------------------
1389 -- Expand_Min_Max_Attribute --
1390 ------------------------------
1392 procedure Expand_Min_Max_Attribute
(N
: Node_Id
) is
1394 -- Min and Max are handled by the back end (except that static cases
1395 -- have already been evaluated during semantic processing, although the
1396 -- back end should not count on this). The one bit of special processing
1397 -- required in the normal case is that these two attributes typically
1398 -- generate conditionals in the code, so check the relevant restriction.
1400 Check_Restriction
(No_Implicit_Conditionals
, N
);
1402 -- In Modify_Tree_For_C mode, we rewrite as an if expression
1404 if Modify_Tree_For_C
then
1406 Loc
: constant Source_Ptr
:= Sloc
(N
);
1407 Typ
: constant Entity_Id
:= Etype
(N
);
1408 Expr
: constant Node_Id
:= First
(Expressions
(N
));
1409 Left
: constant Node_Id
:= Relocate_Node
(Expr
);
1410 Right
: constant Node_Id
:= Relocate_Node
(Next
(Expr
));
1412 function Make_Compare
(Left
, Right
: Node_Id
) return Node_Id
;
1413 -- Returns Left >= Right for Max, Left <= Right for Min
1419 function Make_Compare
(Left
, Right
: Node_Id
) return Node_Id
is
1421 if Attribute_Name
(N
) = Name_Max
then
1425 Right_Opnd
=> Right
);
1430 Right_Opnd
=> Right
);
1434 -- Start of processing for Min_Max
1437 -- If both Left and Right are side effect free, then we can just
1438 -- use Duplicate_Expr to duplicate the references and return
1440 -- (if Left >=|<= Right then Left else Right)
1442 if Side_Effect_Free
(Left
) and then Side_Effect_Free
(Right
) then
1444 Make_If_Expression
(Loc
,
1445 Expressions
=> New_List
(
1446 Make_Compare
(Left
, Right
),
1447 Duplicate_Subexpr_No_Checks
(Left
),
1448 Duplicate_Subexpr_No_Checks
(Right
))));
1450 -- Otherwise we generate declarations to capture the values. We
1451 -- can't put these declarations inside the if expression, since
1452 -- we could end up with an N_Expression_With_Actions which has
1453 -- declarations in the actions, forbidden for Modify_Tree_For_C.
1455 -- The translation is
1457 -- T1 : styp; -- inserted high up in tree
1458 -- T2 : styp; -- inserted high up in tree
1461 -- T1 := styp!(Left);
1462 -- T2 := styp!(Right);
1464 -- (if T1 >=|<= T2 then typ!(T1) else typ!(T2))
1467 -- We insert the T1,T2 declarations with Insert_Declaration which
1468 -- inserts these declarations high up in the tree unconditionally.
1469 -- This is safe since no code is associated with the declarations.
1470 -- Here styp is a standard type whose Esize matches the size of
1471 -- our type. We do this because the actual type may be a result of
1472 -- some local declaration which would not be visible at the point
1473 -- where we insert the declarations of T1 and T2.
1477 T1
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', Left
);
1478 T2
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', Left
);
1479 Styp
: constant Entity_Id
:= Matching_Standard_Type
(Typ
);
1482 Insert_Declaration
(N
,
1483 Make_Object_Declaration
(Loc
,
1484 Defining_Identifier
=> T1
,
1485 Object_Definition
=> New_Occurrence_Of
(Styp
, Loc
)));
1487 Insert_Declaration
(N
,
1488 Make_Object_Declaration
(Loc
,
1489 Defining_Identifier
=> T2
,
1490 Object_Definition
=> New_Occurrence_Of
(Styp
, Loc
)));
1493 Make_Expression_With_Actions
(Loc
,
1494 Actions
=> New_List
(
1495 Make_Assignment_Statement
(Loc
,
1496 Name
=> New_Occurrence_Of
(T1
, Loc
),
1497 Expression
=> Unchecked_Convert_To
(Styp
, Left
)),
1498 Make_Assignment_Statement
(Loc
,
1499 Name
=> New_Occurrence_Of
(T2
, Loc
),
1500 Expression
=> Unchecked_Convert_To
(Styp
, Right
))),
1503 Make_If_Expression
(Loc
,
1504 Expressions
=> New_List
(
1506 (New_Occurrence_Of
(T1
, Loc
),
1507 New_Occurrence_Of
(T2
, Loc
)),
1508 Unchecked_Convert_To
(Typ
,
1509 New_Occurrence_Of
(T1
, Loc
)),
1510 Unchecked_Convert_To
(Typ
,
1511 New_Occurrence_Of
(T2
, Loc
))))));
1515 Analyze_And_Resolve
(N
, Typ
);
1518 end Expand_Min_Max_Attribute
;
1520 ----------------------------------
1521 -- Expand_N_Attribute_Reference --
1522 ----------------------------------
1524 procedure Expand_N_Attribute_Reference
(N
: Node_Id
) is
1525 Loc
: constant Source_Ptr
:= Sloc
(N
);
1526 Typ
: constant Entity_Id
:= Etype
(N
);
1527 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
1528 Pref
: constant Node_Id
:= Prefix
(N
);
1529 Ptyp
: constant Entity_Id
:= Etype
(Pref
);
1530 Exprs
: constant List_Id
:= Expressions
(N
);
1531 Id
: constant Attribute_Id
:= Get_Attribute_Id
(Attribute_Name
(N
));
1533 procedure Rewrite_Stream_Proc_Call
(Pname
: Entity_Id
);
1534 -- Rewrites a stream attribute for Read, Write or Output with the
1535 -- procedure call. Pname is the entity for the procedure to call.
1537 ------------------------------
1538 -- Rewrite_Stream_Proc_Call --
1539 ------------------------------
1541 procedure Rewrite_Stream_Proc_Call
(Pname
: Entity_Id
) is
1542 Item
: constant Node_Id
:= Next
(First
(Exprs
));
1543 Formal
: constant Entity_Id
:= Next_Formal
(First_Formal
(Pname
));
1544 Formal_Typ
: constant Entity_Id
:= Etype
(Formal
);
1545 Is_Written
: constant Boolean := (Ekind
(Formal
) /= E_In_Parameter
);
1548 -- The expansion depends on Item, the second actual, which is
1549 -- the object being streamed in or out.
1551 -- If the item is a component of a packed array type, and
1552 -- a conversion is needed on exit, we introduce a temporary to
1553 -- hold the value, because otherwise the packed reference will
1554 -- not be properly expanded.
1556 if Nkind
(Item
) = N_Indexed_Component
1557 and then Is_Packed
(Base_Type
(Etype
(Prefix
(Item
))))
1558 and then Base_Type
(Etype
(Item
)) /= Base_Type
(Formal_Typ
)
1562 Temp
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
1568 Make_Object_Declaration
(Loc
,
1569 Defining_Identifier
=> Temp
,
1570 Object_Definition
=>
1571 New_Occurrence_Of
(Formal_Typ
, Loc
));
1572 Set_Etype
(Temp
, Formal_Typ
);
1575 Make_Assignment_Statement
(Loc
,
1576 Name
=> New_Copy_Tree
(Item
),
1578 Unchecked_Convert_To
1579 (Etype
(Item
), New_Occurrence_Of
(Temp
, Loc
)));
1581 Rewrite
(Item
, New_Occurrence_Of
(Temp
, Loc
));
1585 Make_Procedure_Call_Statement
(Loc
,
1586 Name
=> New_Occurrence_Of
(Pname
, Loc
),
1587 Parameter_Associations
=> Exprs
),
1590 Rewrite
(N
, Make_Null_Statement
(Loc
));
1595 -- For the class-wide dispatching cases, and for cases in which
1596 -- the base type of the second argument matches the base type of
1597 -- the corresponding formal parameter (that is to say the stream
1598 -- operation is not inherited), we are all set, and can use the
1599 -- argument unchanged.
1601 -- For all other cases we do an unchecked conversion of the second
1602 -- parameter to the type of the formal of the procedure we are
1603 -- calling. This deals with the private type cases, and with going
1604 -- to the root type as required in elementary type case.
1606 if not Is_Class_Wide_Type
(Entity
(Pref
))
1607 and then not Is_Class_Wide_Type
(Etype
(Item
))
1608 and then Base_Type
(Etype
(Item
)) /= Base_Type
(Formal_Typ
)
1611 Unchecked_Convert_To
(Formal_Typ
, Relocate_Node
(Item
)));
1613 -- For untagged derived types set Assignment_OK, to prevent
1614 -- copies from being created when the unchecked conversion
1615 -- is expanded (which would happen in Remove_Side_Effects
1616 -- if Expand_N_Unchecked_Conversion were allowed to call
1617 -- Force_Evaluation). The copy could violate Ada semantics in
1618 -- cases such as an actual that is an out parameter. Note that
1619 -- this approach is also used in exp_ch7 for calls to controlled
1620 -- type operations to prevent problems with actuals wrapped in
1621 -- unchecked conversions.
1623 if Is_Untagged_Derivation
(Etype
(Expression
(Item
))) then
1624 Set_Assignment_OK
(Item
);
1628 -- The stream operation to call may be a renaming created by an
1629 -- attribute definition clause, and may not be frozen yet. Ensure
1630 -- that it has the necessary extra formals.
1632 if not Is_Frozen
(Pname
) then
1633 Create_Extra_Formals
(Pname
);
1636 -- And now rewrite the call
1639 Make_Procedure_Call_Statement
(Loc
,
1640 Name
=> New_Occurrence_Of
(Pname
, Loc
),
1641 Parameter_Associations
=> Exprs
));
1644 end Rewrite_Stream_Proc_Call
;
1646 -- Start of processing for Expand_N_Attribute_Reference
1649 -- Do required validity checking, if enabled. Do not apply check to
1650 -- output parameters of an Asm instruction, since the value of this
1651 -- is not set till after the attribute has been elaborated, and do
1652 -- not apply the check to the arguments of a 'Read or 'Input attribute
1653 -- reference since the scalar argument is an OUT scalar.
1655 if Validity_Checks_On
and then Validity_Check_Operands
1656 and then Id
/= Attribute_Asm_Output
1657 and then Id
/= Attribute_Read
1658 and then Id
/= Attribute_Input
1663 Expr
:= First
(Expressions
(N
));
1664 while Present
(Expr
) loop
1665 Ensure_Valid
(Expr
);
1671 -- Ada 2005 (AI-318-02): If attribute prefix is a call to a build-in-
1672 -- place function, then a temporary return object needs to be created
1673 -- and access to it must be passed to the function. Currently we limit
1674 -- such functions to those with inherently limited result subtypes, but
1675 -- eventually we plan to expand the functions that are treated as
1676 -- build-in-place to include other composite result types.
1678 if Ada_Version
>= Ada_2005
1679 and then Is_Build_In_Place_Function_Call
(Pref
)
1681 Make_Build_In_Place_Call_In_Anonymous_Context
(Pref
);
1684 -- If prefix is a protected type name, this is a reference to the
1685 -- current instance of the type. For a component definition, nothing
1686 -- to do (expansion will occur in the init proc). In other contexts,
1687 -- rewrite into reference to current instance.
1689 if Is_Protected_Self_Reference
(Pref
)
1691 (Nkind_In
(Parent
(N
), N_Index_Or_Discriminant_Constraint
,
1692 N_Discriminant_Association
)
1693 and then Nkind
(Parent
(Parent
(Parent
(Parent
(N
))))) =
1694 N_Component_Definition
)
1696 -- No action needed for these attributes since the current instance
1697 -- will be rewritten to be the name of the _object parameter
1698 -- associated with the enclosing protected subprogram (see below).
1700 and then Id
/= Attribute_Access
1701 and then Id
/= Attribute_Unchecked_Access
1702 and then Id
/= Attribute_Unrestricted_Access
1704 Rewrite
(Pref
, Concurrent_Ref
(Pref
));
1708 -- Remaining processing depends on specific attribute
1710 -- Note: individual sections of the following case statement are
1711 -- allowed to assume there is no code after the case statement, and
1712 -- are legitimately allowed to execute return statements if they have
1713 -- nothing more to do.
1717 -- Attributes related to Ada 2012 iterators
1719 when Attribute_Constant_Indexing |
1720 Attribute_Default_Iterator |
1721 Attribute_Implicit_Dereference |
1722 Attribute_Iterable |
1723 Attribute_Iterator_Element |
1724 Attribute_Variable_Indexing
=>
1727 -- Internal attributes used to deal with Ada 2012 delayed aspects. These
1728 -- were already rejected by the parser. Thus they shouldn't appear here.
1730 when Internal_Attribute_Id
=>
1731 raise Program_Error
;
1737 when Attribute_Access |
1738 Attribute_Unchecked_Access |
1739 Attribute_Unrestricted_Access
=>
1741 Access_Cases
: declare
1742 Ref_Object
: constant Node_Id
:= Get_Referenced_Object
(Pref
);
1743 Btyp_DDT
: Entity_Id
;
1745 function Enclosing_Object
(N
: Node_Id
) return Node_Id
;
1746 -- If N denotes a compound name (selected component, indexed
1747 -- component, or slice), returns the name of the outermost such
1748 -- enclosing object. Otherwise returns N. If the object is a
1749 -- renaming, then the renamed object is returned.
1751 ----------------------
1752 -- Enclosing_Object --
1753 ----------------------
1755 function Enclosing_Object
(N
: Node_Id
) return Node_Id
is
1760 while Nkind_In
(Obj_Name
, N_Selected_Component
,
1761 N_Indexed_Component
,
1764 Obj_Name
:= Prefix
(Obj_Name
);
1767 return Get_Referenced_Object
(Obj_Name
);
1768 end Enclosing_Object
;
1770 -- Local declarations
1772 Enc_Object
: constant Node_Id
:= Enclosing_Object
(Ref_Object
);
1774 -- Start of processing for Access_Cases
1777 Btyp_DDT
:= Designated_Type
(Btyp
);
1779 -- Handle designated types that come from the limited view
1781 if Ekind
(Btyp_DDT
) = E_Incomplete_Type
1782 and then From_Limited_With
(Btyp_DDT
)
1783 and then Present
(Non_Limited_View
(Btyp_DDT
))
1785 Btyp_DDT
:= Non_Limited_View
(Btyp_DDT
);
1787 elsif Is_Class_Wide_Type
(Btyp_DDT
)
1788 and then Ekind
(Etype
(Btyp_DDT
)) = E_Incomplete_Type
1789 and then From_Limited_With
(Etype
(Btyp_DDT
))
1790 and then Present
(Non_Limited_View
(Etype
(Btyp_DDT
)))
1791 and then Present
(Class_Wide_Type
1792 (Non_Limited_View
(Etype
(Btyp_DDT
))))
1795 Class_Wide_Type
(Non_Limited_View
(Etype
(Btyp_DDT
)));
1798 -- In order to improve the text of error messages, the designated
1799 -- type of access-to-subprogram itypes is set by the semantics as
1800 -- the associated subprogram entity (see sem_attr). Now we replace
1801 -- such node with the proper E_Subprogram_Type itype.
1803 if Id
= Attribute_Unrestricted_Access
1804 and then Is_Subprogram
(Directly_Designated_Type
(Typ
))
1806 -- The following conditions ensure that this special management
1807 -- is done only for "Address!(Prim'Unrestricted_Access)" nodes.
1808 -- At this stage other cases in which the designated type is
1809 -- still a subprogram (instead of an E_Subprogram_Type) are
1810 -- wrong because the semantics must have overridden the type of
1811 -- the node with the type imposed by the context.
1813 if Nkind
(Parent
(N
)) = N_Unchecked_Type_Conversion
1814 and then Etype
(Parent
(N
)) = RTE
(RE_Prim_Ptr
)
1816 Set_Etype
(N
, RTE
(RE_Prim_Ptr
));
1820 Subp
: constant Entity_Id
:=
1821 Directly_Designated_Type
(Typ
);
1823 Extra
: Entity_Id
:= Empty
;
1824 New_Formal
: Entity_Id
;
1825 Old_Formal
: Entity_Id
:= First_Formal
(Subp
);
1826 Subp_Typ
: Entity_Id
;
1829 Subp_Typ
:= Create_Itype
(E_Subprogram_Type
, N
);
1830 Set_Etype
(Subp_Typ
, Etype
(Subp
));
1831 Set_Returns_By_Ref
(Subp_Typ
, Returns_By_Ref
(Subp
));
1833 if Present
(Old_Formal
) then
1834 New_Formal
:= New_Copy
(Old_Formal
);
1835 Set_First_Entity
(Subp_Typ
, New_Formal
);
1838 Set_Scope
(New_Formal
, Subp_Typ
);
1839 Etyp
:= Etype
(New_Formal
);
1841 -- Handle itypes. There is no need to duplicate
1842 -- here the itypes associated with record types
1843 -- (i.e the implicit full view of private types).
1846 and then Ekind
(Base_Type
(Etyp
)) /= E_Record_Type
1848 Extra
:= New_Copy
(Etyp
);
1849 Set_Parent
(Extra
, New_Formal
);
1850 Set_Etype
(New_Formal
, Extra
);
1851 Set_Scope
(Extra
, Subp_Typ
);
1854 Extra
:= New_Formal
;
1855 Next_Formal
(Old_Formal
);
1856 exit when No
(Old_Formal
);
1858 Set_Next_Entity
(New_Formal
,
1859 New_Copy
(Old_Formal
));
1860 Next_Entity
(New_Formal
);
1863 Set_Next_Entity
(New_Formal
, Empty
);
1864 Set_Last_Entity
(Subp_Typ
, Extra
);
1867 -- Now that the explicit formals have been duplicated,
1868 -- any extra formals needed by the subprogram must be
1871 if Present
(Extra
) then
1872 Set_Extra_Formal
(Extra
, Empty
);
1875 Create_Extra_Formals
(Subp_Typ
);
1876 Set_Directly_Designated_Type
(Typ
, Subp_Typ
);
1881 if Is_Access_Protected_Subprogram_Type
(Btyp
) then
1882 Expand_Access_To_Protected_Op
(N
, Pref
, Typ
);
1884 -- If prefix is a type name, this is a reference to the current
1885 -- instance of the type, within its initialization procedure.
1887 elsif Is_Entity_Name
(Pref
)
1888 and then Is_Type
(Entity
(Pref
))
1895 -- If the current instance name denotes a task type, then
1896 -- the access attribute is rewritten to be the name of the
1897 -- "_task" parameter associated with the task type's task
1898 -- procedure. An unchecked conversion is applied to ensure
1899 -- a type match in cases of expander-generated calls (e.g.
1902 if Is_Task_Type
(Entity
(Pref
)) then
1904 First_Entity
(Get_Task_Body_Procedure
(Entity
(Pref
)));
1905 while Present
(Formal
) loop
1906 exit when Chars
(Formal
) = Name_uTask
;
1907 Next_Entity
(Formal
);
1910 pragma Assert
(Present
(Formal
));
1913 Unchecked_Convert_To
(Typ
,
1914 New_Occurrence_Of
(Formal
, Loc
)));
1917 elsif Is_Protected_Type
(Entity
(Pref
)) then
1919 -- No action needed for current instance located in a
1920 -- component definition (expansion will occur in the
1923 if Is_Protected_Type
(Current_Scope
) then
1926 -- If the current instance reference is located in a
1927 -- protected subprogram or entry then rewrite the access
1928 -- attribute to be the name of the "_object" parameter.
1929 -- An unchecked conversion is applied to ensure a type
1930 -- match in cases of expander-generated calls (e.g. init
1933 -- The code may be nested in a block, so find enclosing
1934 -- scope that is a protected operation.
1941 Subp
:= Current_Scope
;
1942 while Ekind_In
(Subp
, E_Loop
, E_Block
) loop
1943 Subp
:= Scope
(Subp
);
1948 (Protected_Body_Subprogram
(Subp
));
1950 -- For a protected subprogram the _Object parameter
1951 -- is the protected record, so we create an access
1952 -- to it. The _Object parameter of an entry is an
1955 if Ekind
(Subp
) = E_Entry
then
1957 Unchecked_Convert_To
(Typ
,
1958 New_Occurrence_Of
(Formal
, Loc
)));
1963 Unchecked_Convert_To
(Typ
,
1964 Make_Attribute_Reference
(Loc
,
1965 Attribute_Name
=> Name_Unrestricted_Access
,
1967 New_Occurrence_Of
(Formal
, Loc
))));
1968 Analyze_And_Resolve
(N
);
1973 -- The expression must appear in a default expression,
1974 -- (which in the initialization procedure is the right-hand
1975 -- side of an assignment), and not in a discriminant
1980 while Present
(Par
) loop
1981 exit when Nkind
(Par
) = N_Assignment_Statement
;
1983 if Nkind
(Par
) = N_Component_Declaration
then
1987 Par
:= Parent
(Par
);
1990 if Present
(Par
) then
1992 Make_Attribute_Reference
(Loc
,
1993 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
1994 Attribute_Name
=> Attribute_Name
(N
)));
1996 Analyze_And_Resolve
(N
, Typ
);
2001 -- If the prefix of an Access attribute is a dereference of an
2002 -- access parameter (or a renaming of such a dereference, or a
2003 -- subcomponent of such a dereference) and the context is a
2004 -- general access type (including the type of an object or
2005 -- component with an access_definition, but not the anonymous
2006 -- type of an access parameter or access discriminant), then
2007 -- apply an accessibility check to the access parameter. We used
2008 -- to rewrite the access parameter as a type conversion, but that
2009 -- could only be done if the immediate prefix of the Access
2010 -- attribute was the dereference, and didn't handle cases where
2011 -- the attribute is applied to a subcomponent of the dereference,
2012 -- since there's generally no available, appropriate access type
2013 -- to convert to in that case. The attribute is passed as the
2014 -- point to insert the check, because the access parameter may
2015 -- come from a renaming, possibly in a different scope, and the
2016 -- check must be associated with the attribute itself.
2018 elsif Id
= Attribute_Access
2019 and then Nkind
(Enc_Object
) = N_Explicit_Dereference
2020 and then Is_Entity_Name
(Prefix
(Enc_Object
))
2021 and then (Ekind
(Btyp
) = E_General_Access_Type
2022 or else Is_Local_Anonymous_Access
(Btyp
))
2023 and then Ekind
(Entity
(Prefix
(Enc_Object
))) in Formal_Kind
2024 and then Ekind
(Etype
(Entity
(Prefix
(Enc_Object
))))
2025 = E_Anonymous_Access_Type
2026 and then Present
(Extra_Accessibility
2027 (Entity
(Prefix
(Enc_Object
))))
2029 Apply_Accessibility_Check
(Prefix
(Enc_Object
), Typ
, N
);
2031 -- Ada 2005 (AI-251): If the designated type is an interface we
2032 -- add an implicit conversion to force the displacement of the
2033 -- pointer to reference the secondary dispatch table.
2035 elsif Is_Interface
(Btyp_DDT
)
2036 and then (Comes_From_Source
(N
)
2037 or else Comes_From_Source
(Ref_Object
)
2038 or else (Nkind
(Ref_Object
) in N_Has_Chars
2039 and then Chars
(Ref_Object
) = Name_uInit
))
2041 if Nkind
(Ref_Object
) /= N_Explicit_Dereference
then
2043 -- No implicit conversion required if types match, or if
2044 -- the prefix is the class_wide_type of the interface. In
2045 -- either case passing an object of the interface type has
2046 -- already set the pointer correctly.
2048 if Btyp_DDT
= Etype
(Ref_Object
)
2049 or else (Is_Class_Wide_Type
(Etype
(Ref_Object
))
2051 Class_Wide_Type
(Btyp_DDT
) = Etype
(Ref_Object
))
2056 Rewrite
(Prefix
(N
),
2057 Convert_To
(Btyp_DDT
,
2058 New_Copy_Tree
(Prefix
(N
))));
2060 Analyze_And_Resolve
(Prefix
(N
), Btyp_DDT
);
2063 -- When the object is an explicit dereference, convert the
2064 -- dereference's prefix.
2068 Obj_DDT
: constant Entity_Id
:=
2070 (Directly_Designated_Type
2071 (Etype
(Prefix
(Ref_Object
))));
2073 -- No implicit conversion required if designated types
2074 -- match, or if we have an unrestricted access.
2076 if Obj_DDT
/= Btyp_DDT
2077 and then Id
/= Attribute_Unrestricted_Access
2078 and then not (Is_Class_Wide_Type
(Obj_DDT
)
2079 and then Etype
(Obj_DDT
) = Btyp_DDT
)
2083 New_Copy_Tree
(Prefix
(Ref_Object
))));
2084 Analyze_And_Resolve
(N
, Typ
);
2095 -- Transforms 'Adjacent into a call to the floating-point attribute
2096 -- function Adjacent in Fat_xxx (where xxx is the root type)
2098 when Attribute_Adjacent
=>
2099 Expand_Fpt_Attribute_RR
(N
);
2105 when Attribute_Address
=> Address
: declare
2106 Task_Proc
: Entity_Id
;
2109 -- If the prefix is a task or a task type, the useful address is that
2110 -- of the procedure for the task body, i.e. the actual program unit.
2111 -- We replace the original entity with that of the procedure.
2113 if Is_Entity_Name
(Pref
)
2114 and then Is_Task_Type
(Entity
(Pref
))
2116 Task_Proc
:= Next_Entity
(Root_Type
(Ptyp
));
2118 while Present
(Task_Proc
) loop
2119 exit when Ekind
(Task_Proc
) = E_Procedure
2120 and then Etype
(First_Formal
(Task_Proc
)) =
2121 Corresponding_Record_Type
(Ptyp
);
2122 Next_Entity
(Task_Proc
);
2125 if Present
(Task_Proc
) then
2126 Set_Entity
(Pref
, Task_Proc
);
2127 Set_Etype
(Pref
, Etype
(Task_Proc
));
2130 -- Similarly, the address of a protected operation is the address
2131 -- of the corresponding protected body, regardless of the protected
2132 -- object from which it is selected.
2134 elsif Nkind
(Pref
) = N_Selected_Component
2135 and then Is_Subprogram
(Entity
(Selector_Name
(Pref
)))
2136 and then Is_Protected_Type
(Scope
(Entity
(Selector_Name
(Pref
))))
2140 External_Subprogram
(Entity
(Selector_Name
(Pref
))), Loc
));
2142 elsif Nkind
(Pref
) = N_Explicit_Dereference
2143 and then Ekind
(Ptyp
) = E_Subprogram_Type
2144 and then Convention
(Ptyp
) = Convention_Protected
2146 -- The prefix is be a dereference of an access_to_protected_
2147 -- subprogram. The desired address is the second component of
2148 -- the record that represents the access.
2151 Addr
: constant Entity_Id
:= Etype
(N
);
2152 Ptr
: constant Node_Id
:= Prefix
(Pref
);
2153 T
: constant Entity_Id
:=
2154 Equivalent_Type
(Base_Type
(Etype
(Ptr
)));
2158 Unchecked_Convert_To
(Addr
,
2159 Make_Selected_Component
(Loc
,
2160 Prefix
=> Unchecked_Convert_To
(T
, Ptr
),
2161 Selector_Name
=> New_Occurrence_Of
(
2162 Next_Entity
(First_Entity
(T
)), Loc
))));
2164 Analyze_And_Resolve
(N
, Addr
);
2167 -- Ada 2005 (AI-251): Class-wide interface objects are always
2168 -- "displaced" to reference the tag associated with the interface
2169 -- type. In order to obtain the real address of such objects we
2170 -- generate a call to a run-time subprogram that returns the base
2171 -- address of the object.
2173 -- This processing is not needed in the VM case, where dispatching
2174 -- issues are taken care of by the virtual machine.
2176 elsif Is_Class_Wide_Type
(Ptyp
)
2177 and then Is_Interface
(Ptyp
)
2178 and then Tagged_Type_Expansion
2179 and then not (Nkind
(Pref
) in N_Has_Entity
2180 and then Is_Subprogram
(Entity
(Pref
)))
2183 Make_Function_Call
(Loc
,
2184 Name
=> New_Occurrence_Of
(RTE
(RE_Base_Address
), Loc
),
2185 Parameter_Associations
=> New_List
(
2186 Relocate_Node
(N
))));
2191 -- Deal with packed array reference, other cases are handled by
2194 if Involves_Packed_Array_Reference
(Pref
) then
2195 Expand_Packed_Address_Reference
(N
);
2203 when Attribute_Alignment
=> Alignment
: declare
2207 -- For class-wide types, X'Class'Alignment is transformed into a
2208 -- direct reference to the Alignment of the class type, so that the
2209 -- back end does not have to deal with the X'Class'Alignment
2212 if Is_Entity_Name
(Pref
)
2213 and then Is_Class_Wide_Type
(Entity
(Pref
))
2215 Rewrite
(Prefix
(N
), New_Occurrence_Of
(Entity
(Pref
), Loc
));
2218 -- For x'Alignment applied to an object of a class wide type,
2219 -- transform X'Alignment into a call to the predefined primitive
2220 -- operation _Alignment applied to X.
2222 elsif Is_Class_Wide_Type
(Ptyp
) then
2224 Make_Attribute_Reference
(Loc
,
2226 Attribute_Name
=> Name_Tag
);
2228 if VM_Target
= No_VM
then
2229 New_Node
:= Build_Get_Alignment
(Loc
, New_Node
);
2232 Make_Function_Call
(Loc
,
2233 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Alignment
), Loc
),
2234 Parameter_Associations
=> New_List
(New_Node
));
2237 -- Case where the context is a specific integer type with which
2238 -- the original attribute was compatible. The function has a
2239 -- specific type as well, so to preserve the compatibility we
2240 -- must convert explicitly.
2242 if Typ
/= Standard_Integer
then
2243 New_Node
:= Convert_To
(Typ
, New_Node
);
2246 Rewrite
(N
, New_Node
);
2247 Analyze_And_Resolve
(N
, Typ
);
2250 -- For all other cases, we just have to deal with the case of
2251 -- the fact that the result can be universal.
2254 Apply_Universal_Integer_Attribute_Checks
(N
);
2262 -- We compute this if a packed array reference was present, otherwise we
2263 -- leave the computation up to the back end.
2265 when Attribute_Bit
=>
2266 if Involves_Packed_Array_Reference
(Pref
) then
2267 Expand_Packed_Bit_Reference
(N
);
2269 Apply_Universal_Integer_Attribute_Checks
(N
);
2276 -- We compute this if a component clause was present, otherwise we leave
2277 -- the computation up to the back end, since we don't know what layout
2280 -- Note that the attribute can apply to a naked record component
2281 -- in generated code (i.e. the prefix is an identifier that
2282 -- references the component or discriminant entity).
2284 when Attribute_Bit_Position
=> Bit_Position
: declare
2288 if Nkind
(Pref
) = N_Identifier
then
2289 CE
:= Entity
(Pref
);
2291 CE
:= Entity
(Selector_Name
(Pref
));
2294 if Known_Static_Component_Bit_Offset
(CE
) then
2296 Make_Integer_Literal
(Loc
,
2297 Intval
=> Component_Bit_Offset
(CE
)));
2298 Analyze_And_Resolve
(N
, Typ
);
2301 Apply_Universal_Integer_Attribute_Checks
(N
);
2309 -- A reference to P'Body_Version or P'Version is expanded to
2312 -- pragma Import (C, Vnn, "uuuuT");
2314 -- Get_Version_String (Vnn)
2316 -- where uuuu is the unit name (dots replaced by double underscore)
2317 -- and T is B for the cases of Body_Version, or Version applied to a
2318 -- subprogram acting as its own spec, and S for Version applied to a
2319 -- subprogram spec or package. This sequence of code references the
2320 -- unsigned constant created in the main program by the binder.
2322 -- A special exception occurs for Standard, where the string returned
2323 -- is a copy of the library string in gnatvsn.ads.
2325 when Attribute_Body_Version | Attribute_Version
=> Version
: declare
2326 E
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
2331 -- If not library unit, get to containing library unit
2333 Pent
:= Entity
(Pref
);
2334 while Pent
/= Standard_Standard
2335 and then Scope
(Pent
) /= Standard_Standard
2336 and then not Is_Child_Unit
(Pent
)
2338 Pent
:= Scope
(Pent
);
2341 -- Special case Standard and Standard.ASCII
2343 if Pent
= Standard_Standard
or else Pent
= Standard_ASCII
then
2345 Make_String_Literal
(Loc
,
2346 Strval
=> Verbose_Library_Version
));
2351 -- Build required string constant
2353 Get_Name_String
(Get_Unit_Name
(Pent
));
2356 for J
in 1 .. Name_Len
- 2 loop
2357 if Name_Buffer
(J
) = '.' then
2358 Store_String_Chars
("__");
2360 Store_String_Char
(Get_Char_Code
(Name_Buffer
(J
)));
2364 -- Case of subprogram acting as its own spec, always use body
2366 if Nkind
(Declaration_Node
(Pent
)) in N_Subprogram_Specification
2367 and then Nkind
(Parent
(Declaration_Node
(Pent
))) =
2369 and then Acts_As_Spec
(Parent
(Declaration_Node
(Pent
)))
2371 Store_String_Chars
("B");
2373 -- Case of no body present, always use spec
2375 elsif not Unit_Requires_Body
(Pent
) then
2376 Store_String_Chars
("S");
2378 -- Otherwise use B for Body_Version, S for spec
2380 elsif Id
= Attribute_Body_Version
then
2381 Store_String_Chars
("B");
2383 Store_String_Chars
("S");
2387 Lib
.Version_Referenced
(S
);
2389 -- Insert the object declaration
2391 Insert_Actions
(N
, New_List
(
2392 Make_Object_Declaration
(Loc
,
2393 Defining_Identifier
=> E
,
2394 Object_Definition
=>
2395 New_Occurrence_Of
(RTE
(RE_Unsigned
), Loc
))));
2397 -- Set entity as imported with correct external name
2399 Set_Is_Imported
(E
);
2400 Set_Interface_Name
(E
, Make_String_Literal
(Loc
, S
));
2402 -- Set entity as internal to ensure proper Sprint output of its
2403 -- implicit importation.
2405 Set_Is_Internal
(E
);
2407 -- And now rewrite original reference
2410 Make_Function_Call
(Loc
,
2411 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Version_String
), Loc
),
2412 Parameter_Associations
=> New_List
(
2413 New_Occurrence_Of
(E
, Loc
))));
2416 Analyze_And_Resolve
(N
, RTE
(RE_Version_String
));
2423 -- Transforms 'Ceiling into a call to the floating-point attribute
2424 -- function Ceiling in Fat_xxx (where xxx is the root type)
2426 when Attribute_Ceiling
=>
2427 Expand_Fpt_Attribute_R
(N
);
2433 -- Transforms 'Callable attribute into a call to the Callable function
2435 when Attribute_Callable
=> Callable
:
2437 -- We have an object of a task interface class-wide type as a prefix
2438 -- to Callable. Generate:
2439 -- callable (Task_Id (Pref._disp_get_task_id));
2441 if Ada_Version
>= Ada_2005
2442 and then Ekind
(Ptyp
) = E_Class_Wide_Type
2443 and then Is_Interface
(Ptyp
)
2444 and then Is_Task_Interface
(Ptyp
)
2447 Make_Function_Call
(Loc
,
2449 New_Occurrence_Of
(RTE
(RE_Callable
), Loc
),
2450 Parameter_Associations
=> New_List
(
2451 Make_Unchecked_Type_Conversion
(Loc
,
2453 New_Occurrence_Of
(RTE
(RO_ST_Task_Id
), Loc
),
2455 Make_Selected_Component
(Loc
,
2457 New_Copy_Tree
(Pref
),
2459 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
))))));
2463 Build_Call_With_Task
(Pref
, RTE
(RE_Callable
)));
2466 Analyze_And_Resolve
(N
, Standard_Boolean
);
2473 -- Transforms 'Caller attribute into a call to either the
2474 -- Task_Entry_Caller or the Protected_Entry_Caller function.
2476 when Attribute_Caller
=> Caller
: declare
2477 Id_Kind
: constant Entity_Id
:= RTE
(RO_AT_Task_Id
);
2478 Ent
: constant Entity_Id
:= Entity
(Pref
);
2479 Conctype
: constant Entity_Id
:= Scope
(Ent
);
2480 Nest_Depth
: Integer := 0;
2487 if Is_Protected_Type
(Conctype
) then
2488 case Corresponding_Runtime_Package
(Conctype
) is
2489 when System_Tasking_Protected_Objects_Entries
=>
2492 (RTE
(RE_Protected_Entry_Caller
), Loc
);
2494 when System_Tasking_Protected_Objects_Single_Entry
=>
2497 (RTE
(RE_Protected_Single_Entry_Caller
), Loc
);
2500 raise Program_Error
;
2504 Unchecked_Convert_To
(Id_Kind
,
2505 Make_Function_Call
(Loc
,
2507 Parameter_Associations
=> New_List
(
2509 (Find_Protection_Object
(Current_Scope
), Loc
)))));
2514 -- Determine the nesting depth of the E'Caller attribute, that
2515 -- is, how many accept statements are nested within the accept
2516 -- statement for E at the point of E'Caller. The runtime uses
2517 -- this depth to find the specified entry call.
2519 for J
in reverse 0 .. Scope_Stack
.Last
loop
2520 S
:= Scope_Stack
.Table
(J
).Entity
;
2522 -- We should not reach the scope of the entry, as it should
2523 -- already have been checked in Sem_Attr that this attribute
2524 -- reference is within a matching accept statement.
2526 pragma Assert
(S
/= Conctype
);
2531 elsif Is_Entry
(S
) then
2532 Nest_Depth
:= Nest_Depth
+ 1;
2537 Unchecked_Convert_To
(Id_Kind
,
2538 Make_Function_Call
(Loc
,
2540 New_Occurrence_Of
(RTE
(RE_Task_Entry_Caller
), Loc
),
2541 Parameter_Associations
=> New_List
(
2542 Make_Integer_Literal
(Loc
,
2543 Intval
=> Int
(Nest_Depth
))))));
2546 Analyze_And_Resolve
(N
, Id_Kind
);
2553 -- Transforms 'Compose into a call to the floating-point attribute
2554 -- function Compose in Fat_xxx (where xxx is the root type)
2556 -- Note: we strictly should have special code here to deal with the
2557 -- case of absurdly negative arguments (less than Integer'First)
2558 -- which will return a (signed) zero value, but it hardly seems
2559 -- worth the effort. Absurdly large positive arguments will raise
2560 -- constraint error which is fine.
2562 when Attribute_Compose
=>
2563 Expand_Fpt_Attribute_RI
(N
);
2569 when Attribute_Constrained
=> Constrained
: declare
2570 Formal_Ent
: constant Entity_Id
:= Param_Entity
(Pref
);
2572 function Is_Constrained_Aliased_View
(Obj
: Node_Id
) return Boolean;
2573 -- Ada 2005 (AI-363): Returns True if the object name Obj denotes a
2574 -- view of an aliased object whose subtype is constrained.
2576 ---------------------------------
2577 -- Is_Constrained_Aliased_View --
2578 ---------------------------------
2580 function Is_Constrained_Aliased_View
(Obj
: Node_Id
) return Boolean is
2584 if Is_Entity_Name
(Obj
) then
2587 if Present
(Renamed_Object
(E
)) then
2588 return Is_Constrained_Aliased_View
(Renamed_Object
(E
));
2590 return Is_Aliased
(E
) and then Is_Constrained
(Etype
(E
));
2594 return Is_Aliased_View
(Obj
)
2596 (Is_Constrained
(Etype
(Obj
))
2598 (Nkind
(Obj
) = N_Explicit_Dereference
2600 not Object_Type_Has_Constrained_Partial_View
2601 (Typ
=> Base_Type
(Etype
(Obj
)),
2602 Scop
=> Current_Scope
)));
2604 end Is_Constrained_Aliased_View
;
2606 -- Start of processing for Constrained
2609 -- Reference to a parameter where the value is passed as an extra
2610 -- actual, corresponding to the extra formal referenced by the
2611 -- Extra_Constrained field of the corresponding formal. If this
2612 -- is an entry in-parameter, it is replaced by a constant renaming
2613 -- for which Extra_Constrained is never created.
2615 if Present
(Formal_Ent
)
2616 and then Ekind
(Formal_Ent
) /= E_Constant
2617 and then Present
(Extra_Constrained
(Formal_Ent
))
2621 (Extra_Constrained
(Formal_Ent
), Sloc
(N
)));
2623 -- For variables with a Extra_Constrained field, we use the
2624 -- corresponding entity.
2626 elsif Nkind
(Pref
) = N_Identifier
2627 and then Ekind
(Entity
(Pref
)) = E_Variable
2628 and then Present
(Extra_Constrained
(Entity
(Pref
)))
2632 (Extra_Constrained
(Entity
(Pref
)), Sloc
(N
)));
2634 -- For all other entity names, we can tell at compile time
2636 elsif Is_Entity_Name
(Pref
) then
2638 Ent
: constant Entity_Id
:= Entity
(Pref
);
2642 -- (RM J.4) obsolescent cases
2644 if Is_Type
(Ent
) then
2648 if Is_Private_Type
(Ent
) then
2649 Res
:= not Has_Discriminants
(Ent
)
2650 or else Is_Constrained
(Ent
);
2652 -- It not a private type, must be a generic actual type
2653 -- that corresponded to a private type. We know that this
2654 -- correspondence holds, since otherwise the reference
2655 -- within the generic template would have been illegal.
2658 if Is_Composite_Type
(Underlying_Type
(Ent
)) then
2659 Res
:= Is_Constrained
(Ent
);
2665 -- If the prefix is not a variable or is aliased, then
2666 -- definitely true; if it's a formal parameter without an
2667 -- associated extra formal, then treat it as constrained.
2669 -- Ada 2005 (AI-363): An aliased prefix must be known to be
2670 -- constrained in order to set the attribute to True.
2672 elsif not Is_Variable
(Pref
)
2673 or else Present
(Formal_Ent
)
2674 or else (Ada_Version
< Ada_2005
2675 and then Is_Aliased_View
(Pref
))
2676 or else (Ada_Version
>= Ada_2005
2677 and then Is_Constrained_Aliased_View
(Pref
))
2681 -- Variable case, look at type to see if it is constrained.
2682 -- Note that the one case where this is not accurate (the
2683 -- procedure formal case), has been handled above.
2685 -- We use the Underlying_Type here (and below) in case the
2686 -- type is private without discriminants, but the full type
2687 -- has discriminants. This case is illegal, but we generate it
2688 -- internally for passing to the Extra_Constrained parameter.
2691 -- In Ada 2012, test for case of a limited tagged type, in
2692 -- which case the attribute is always required to return
2693 -- True. The underlying type is tested, to make sure we also
2694 -- return True for cases where there is an unconstrained
2695 -- object with an untagged limited partial view which has
2696 -- defaulted discriminants (such objects always produce a
2697 -- False in earlier versions of Ada). (Ada 2012: AI05-0214)
2699 Res
:= Is_Constrained
(Underlying_Type
(Etype
(Ent
)))
2701 (Ada_Version
>= Ada_2012
2702 and then Is_Tagged_Type
(Underlying_Type
(Ptyp
))
2703 and then Is_Limited_Type
(Ptyp
));
2706 Rewrite
(N
, New_Occurrence_Of
(Boolean_Literals
(Res
), Loc
));
2709 -- Prefix is not an entity name. These are also cases where we can
2710 -- always tell at compile time by looking at the form and type of the
2711 -- prefix. If an explicit dereference of an object with constrained
2712 -- partial view, this is unconstrained (Ada 2005: AI95-0363). If the
2713 -- underlying type is a limited tagged type, then Constrained is
2714 -- required to always return True (Ada 2012: AI05-0214).
2720 not Is_Variable
(Pref
)
2722 (Nkind
(Pref
) = N_Explicit_Dereference
2724 not Object_Type_Has_Constrained_Partial_View
2725 (Typ
=> Base_Type
(Ptyp
),
2726 Scop
=> Current_Scope
))
2727 or else Is_Constrained
(Underlying_Type
(Ptyp
))
2728 or else (Ada_Version
>= Ada_2012
2729 and then Is_Tagged_Type
(Underlying_Type
(Ptyp
))
2730 and then Is_Limited_Type
(Ptyp
))),
2734 Analyze_And_Resolve
(N
, Standard_Boolean
);
2741 -- Transforms 'Copy_Sign into a call to the floating-point attribute
2742 -- function Copy_Sign in Fat_xxx (where xxx is the root type)
2744 when Attribute_Copy_Sign
=>
2745 Expand_Fpt_Attribute_RR
(N
);
2751 -- Transforms 'Count attribute into a call to the Count function
2753 when Attribute_Count
=> Count
: declare
2755 Conctyp
: Entity_Id
;
2757 Entry_Id
: Entity_Id
;
2762 -- If the prefix is a member of an entry family, retrieve both
2763 -- entry name and index. For a simple entry there is no index.
2765 if Nkind
(Pref
) = N_Indexed_Component
then
2766 Entnam
:= Prefix
(Pref
);
2767 Index
:= First
(Expressions
(Pref
));
2773 Entry_Id
:= Entity
(Entnam
);
2775 -- Find the concurrent type in which this attribute is referenced
2776 -- (there had better be one).
2778 Conctyp
:= Current_Scope
;
2779 while not Is_Concurrent_Type
(Conctyp
) loop
2780 Conctyp
:= Scope
(Conctyp
);
2785 if Is_Protected_Type
(Conctyp
) then
2786 case Corresponding_Runtime_Package
(Conctyp
) is
2787 when System_Tasking_Protected_Objects_Entries
=>
2788 Name
:= New_Occurrence_Of
(RTE
(RE_Protected_Count
), Loc
);
2791 Make_Function_Call
(Loc
,
2793 Parameter_Associations
=> New_List
(
2795 (Find_Protection_Object
(Current_Scope
), Loc
),
2796 Entry_Index_Expression
2797 (Loc
, Entry_Id
, Index
, Scope
(Entry_Id
))));
2799 when System_Tasking_Protected_Objects_Single_Entry
=>
2801 New_Occurrence_Of
(RTE
(RE_Protected_Count_Entry
), Loc
);
2804 Make_Function_Call
(Loc
,
2806 Parameter_Associations
=> New_List
(
2808 (Find_Protection_Object
(Current_Scope
), Loc
)));
2811 raise Program_Error
;
2818 Make_Function_Call
(Loc
,
2819 Name
=> New_Occurrence_Of
(RTE
(RE_Task_Count
), Loc
),
2820 Parameter_Associations
=> New_List
(
2821 Entry_Index_Expression
(Loc
,
2822 Entry_Id
, Index
, Scope
(Entry_Id
))));
2825 -- The call returns type Natural but the context is universal integer
2826 -- so any integer type is allowed. The attribute was already resolved
2827 -- so its Etype is the required result type. If the base type of the
2828 -- context type is other than Standard.Integer we put in a conversion
2829 -- to the required type. This can be a normal typed conversion since
2830 -- both input and output types of the conversion are integer types
2832 if Base_Type
(Typ
) /= Base_Type
(Standard_Integer
) then
2833 Rewrite
(N
, Convert_To
(Typ
, Call
));
2838 Analyze_And_Resolve
(N
, Typ
);
2841 ---------------------
2842 -- Descriptor_Size --
2843 ---------------------
2845 when Attribute_Descriptor_Size
=>
2847 -- Attribute Descriptor_Size is handled by the back end when applied
2848 -- to an unconstrained array type.
2850 if Is_Array_Type
(Ptyp
)
2851 and then not Is_Constrained
(Ptyp
)
2853 Apply_Universal_Integer_Attribute_Checks
(N
);
2855 -- For any other type, the descriptor size is 0 because there is no
2856 -- actual descriptor, but the result is not formally static.
2859 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
2861 Set_Is_Static_Expression
(N
, False);
2868 -- This processing is shared by Elab_Spec
2870 -- What we do is to insert the following declarations
2873 -- pragma Import (C, enn, "name___elabb/s");
2875 -- and then the Elab_Body/Spec attribute is replaced by a reference
2876 -- to this defining identifier.
2878 when Attribute_Elab_Body |
2879 Attribute_Elab_Spec
=>
2881 -- Leave attribute unexpanded in CodePeer mode: the gnat2scil
2882 -- back-end knows how to handle these attributes directly.
2884 if CodePeer_Mode
then
2889 Ent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'E');
2893 procedure Make_Elab_String
(Nod
: Node_Id
);
2894 -- Given Nod, an identifier, or a selected component, put the
2895 -- image into the current string literal, with double underline
2896 -- between components.
2898 ----------------------
2899 -- Make_Elab_String --
2900 ----------------------
2902 procedure Make_Elab_String
(Nod
: Node_Id
) is
2904 if Nkind
(Nod
) = N_Selected_Component
then
2905 Make_Elab_String
(Prefix
(Nod
));
2909 Store_String_Char
('$');
2911 Store_String_Char
('.');
2913 Store_String_Char
('_');
2914 Store_String_Char
('_');
2917 Get_Name_String
(Chars
(Selector_Name
(Nod
)));
2920 pragma Assert
(Nkind
(Nod
) = N_Identifier
);
2921 Get_Name_String
(Chars
(Nod
));
2924 Store_String_Chars
(Name_Buffer
(1 .. Name_Len
));
2925 end Make_Elab_String
;
2927 -- Start of processing for Elab_Body/Elab_Spec
2930 -- First we need to prepare the string literal for the name of
2931 -- the elaboration routine to be referenced.
2934 Make_Elab_String
(Pref
);
2936 if VM_Target
= No_VM
then
2937 Store_String_Chars
("___elab");
2938 Lang
:= Make_Identifier
(Loc
, Name_C
);
2940 Store_String_Chars
("._elab");
2941 Lang
:= Make_Identifier
(Loc
, Name_Ada
);
2944 if Id
= Attribute_Elab_Body
then
2945 Store_String_Char
('b');
2947 Store_String_Char
('s');
2952 Insert_Actions
(N
, New_List
(
2953 Make_Subprogram_Declaration
(Loc
,
2955 Make_Procedure_Specification
(Loc
,
2956 Defining_Unit_Name
=> Ent
)),
2959 Chars
=> Name_Import
,
2960 Pragma_Argument_Associations
=> New_List
(
2961 Make_Pragma_Argument_Association
(Loc
, Expression
=> Lang
),
2963 Make_Pragma_Argument_Association
(Loc
,
2964 Expression
=> Make_Identifier
(Loc
, Chars
(Ent
))),
2966 Make_Pragma_Argument_Association
(Loc
,
2967 Expression
=> Make_String_Literal
(Loc
, Str
))))));
2969 Set_Entity
(N
, Ent
);
2970 Rewrite
(N
, New_Occurrence_Of
(Ent
, Loc
));
2973 --------------------
2974 -- Elab_Subp_Body --
2975 --------------------
2977 -- Always ignored. In CodePeer mode, gnat2scil knows how to handle
2978 -- this attribute directly, and if we are not in CodePeer mode it is
2979 -- entirely ignored ???
2981 when Attribute_Elab_Subp_Body
=>
2988 -- Elaborated is always True for preelaborated units, predefined units,
2989 -- pure units and units which have Elaborate_Body pragmas. These units
2990 -- have no elaboration entity.
2992 -- Note: The Elaborated attribute is never passed to the back end
2994 when Attribute_Elaborated
=> Elaborated
: declare
2995 Ent
: constant Entity_Id
:= Entity
(Pref
);
2998 if Present
(Elaboration_Entity
(Ent
)) then
3002 New_Occurrence_Of
(Elaboration_Entity
(Ent
), Loc
),
3004 Make_Integer_Literal
(Loc
, Uint_0
)));
3005 Analyze_And_Resolve
(N
, Typ
);
3007 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
3015 when Attribute_Enum_Rep
=> Enum_Rep
:
3017 -- X'Enum_Rep (Y) expands to
3021 -- This is simply a direct conversion from the enumeration type to
3022 -- the target integer type, which is treated by the back end as a
3023 -- normal integer conversion, treating the enumeration type as an
3024 -- integer, which is exactly what we want. We set Conversion_OK to
3025 -- make sure that the analyzer does not complain about what otherwise
3026 -- might be an illegal conversion.
3028 if Is_Non_Empty_List
(Exprs
) then
3030 OK_Convert_To
(Typ
, Relocate_Node
(First
(Exprs
))));
3032 -- X'Enum_Rep where X is an enumeration literal is replaced by
3033 -- the literal value.
3035 elsif Ekind
(Entity
(Pref
)) = E_Enumeration_Literal
then
3037 Make_Integer_Literal
(Loc
, Enumeration_Rep
(Entity
(Pref
))));
3039 -- If this is a renaming of a literal, recover the representation
3042 elsif Ekind
(Entity
(Pref
)) = E_Constant
3043 and then Present
(Renamed_Object
(Entity
(Pref
)))
3045 Ekind
(Entity
(Renamed_Object
(Entity
(Pref
))))
3046 = E_Enumeration_Literal
3049 Make_Integer_Literal
(Loc
,
3050 Enumeration_Rep
(Entity
(Renamed_Object
(Entity
(Pref
))))));
3052 -- X'Enum_Rep where X is an object does a direct unchecked conversion
3053 -- of the object value, as described for the type case above.
3057 OK_Convert_To
(Typ
, Relocate_Node
(Pref
)));
3061 Analyze_And_Resolve
(N
, Typ
);
3068 when Attribute_Enum_Val
=> Enum_Val
: declare
3070 Btyp
: constant Entity_Id
:= Base_Type
(Ptyp
);
3073 -- X'Enum_Val (Y) expands to
3075 -- [constraint_error when _rep_to_pos (Y, False) = -1, msg]
3078 Expr
:= Unchecked_Convert_To
(Ptyp
, First
(Exprs
));
3081 Make_Raise_Constraint_Error
(Loc
,
3085 Make_Function_Call
(Loc
,
3087 New_Occurrence_Of
(TSS
(Btyp
, TSS_Rep_To_Pos
), Loc
),
3088 Parameter_Associations
=> New_List
(
3089 Relocate_Node
(Duplicate_Subexpr
(Expr
)),
3090 New_Occurrence_Of
(Standard_False
, Loc
))),
3092 Right_Opnd
=> Make_Integer_Literal
(Loc
, -1)),
3093 Reason
=> CE_Range_Check_Failed
));
3096 Analyze_And_Resolve
(N
, Ptyp
);
3103 -- Transforms 'Exponent into a call to the floating-point attribute
3104 -- function Exponent in Fat_xxx (where xxx is the root type)
3106 when Attribute_Exponent
=>
3107 Expand_Fpt_Attribute_R
(N
);
3113 -- transforme X'External_Tag into Ada.Tags.External_Tag (X'tag)
3115 when Attribute_External_Tag
=> External_Tag
:
3118 Make_Function_Call
(Loc
,
3119 Name
=> New_Occurrence_Of
(RTE
(RE_External_Tag
), Loc
),
3120 Parameter_Associations
=> New_List
(
3121 Make_Attribute_Reference
(Loc
,
3122 Attribute_Name
=> Name_Tag
,
3123 Prefix
=> Prefix
(N
)))));
3125 Analyze_And_Resolve
(N
, Standard_String
);
3132 when Attribute_First
=>
3134 -- If the prefix type is a constrained packed array type which
3135 -- already has a Packed_Array_Impl_Type representation defined, then
3136 -- replace this attribute with a direct reference to 'First of the
3137 -- appropriate index subtype (since otherwise the back end will try
3138 -- to give us the value of 'First for this implementation type).
3140 if Is_Constrained_Packed_Array
(Ptyp
) then
3142 Make_Attribute_Reference
(Loc
,
3143 Attribute_Name
=> Name_First
,
3145 New_Occurrence_Of
(Get_Index_Subtype
(N
), Loc
)));
3146 Analyze_And_Resolve
(N
, Typ
);
3148 -- For access type, apply access check as needed
3150 elsif Is_Access_Type
(Ptyp
) then
3151 Apply_Access_Check
(N
);
3153 -- For scalar type, if low bound is a reference to an entity, just
3154 -- replace with a direct reference. Note that we can only have a
3155 -- reference to a constant entity at this stage, anything else would
3156 -- have already been rewritten.
3158 elsif Is_Scalar_Type
(Ptyp
) then
3160 Lo
: constant Node_Id
:= Type_Low_Bound
(Ptyp
);
3162 if Is_Entity_Name
(Lo
) then
3163 Rewrite
(N
, New_Occurrence_Of
(Entity
(Lo
), Loc
));
3172 -- Compute this if component clause was present, otherwise we leave the
3173 -- computation to be completed in the back-end, since we don't know what
3174 -- layout will be chosen.
3176 when Attribute_First_Bit
=> First_Bit_Attr
: declare
3177 CE
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
3180 -- In Ada 2005 (or later) if we have the non-default bit order, then
3181 -- we return the original value as given in the component clause
3182 -- (RM 2005 13.5.2(3/2)).
3184 if Present
(Component_Clause
(CE
))
3185 and then Ada_Version
>= Ada_2005
3186 and then Reverse_Bit_Order
(Scope
(CE
))
3189 Make_Integer_Literal
(Loc
,
3190 Intval
=> Expr_Value
(First_Bit
(Component_Clause
(CE
)))));
3191 Analyze_And_Resolve
(N
, Typ
);
3193 -- Otherwise (Ada 83/95 or Ada 2005 or later with default bit order),
3194 -- rewrite with normalized value if we know it statically.
3196 elsif Known_Static_Component_Bit_Offset
(CE
) then
3198 Make_Integer_Literal
(Loc
,
3199 Component_Bit_Offset
(CE
) mod System_Storage_Unit
));
3200 Analyze_And_Resolve
(N
, Typ
);
3202 -- Otherwise left to back end, just do universal integer checks
3205 Apply_Universal_Integer_Attribute_Checks
(N
);
3215 -- fixtype'Fixed_Value (integer-value)
3219 -- fixtype(integer-value)
3221 -- We do all the required analysis of the conversion here, because we do
3222 -- not want this to go through the fixed-point conversion circuits. Note
3223 -- that the back end always treats fixed-point as equivalent to the
3224 -- corresponding integer type anyway.
3226 when Attribute_Fixed_Value
=> Fixed_Value
:
3229 Make_Type_Conversion
(Loc
,
3230 Subtype_Mark
=> New_Occurrence_Of
(Entity
(Pref
), Loc
),
3231 Expression
=> Relocate_Node
(First
(Exprs
))));
3232 Set_Etype
(N
, Entity
(Pref
));
3235 -- Note: it might appear that a properly analyzed unchecked conversion
3236 -- would be just fine here, but that's not the case, since the full
3237 -- range checks performed by the following call are critical.
3239 Apply_Type_Conversion_Checks
(N
);
3246 -- Transforms 'Floor into a call to the floating-point attribute
3247 -- function Floor in Fat_xxx (where xxx is the root type)
3249 when Attribute_Floor
=>
3250 Expand_Fpt_Attribute_R
(N
);
3256 -- For the fixed-point type Typ:
3262 -- Result_Type (System.Fore (Universal_Real (Type'First)),
3263 -- Universal_Real (Type'Last))
3265 -- Note that we know that the type is a non-static subtype, or Fore
3266 -- would have itself been computed dynamically in Eval_Attribute.
3268 when Attribute_Fore
=> Fore
: begin
3271 Make_Function_Call
(Loc
,
3272 Name
=> New_Occurrence_Of
(RTE
(RE_Fore
), Loc
),
3274 Parameter_Associations
=> New_List
(
3275 Convert_To
(Universal_Real
,
3276 Make_Attribute_Reference
(Loc
,
3277 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
3278 Attribute_Name
=> Name_First
)),
3280 Convert_To
(Universal_Real
,
3281 Make_Attribute_Reference
(Loc
,
3282 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
3283 Attribute_Name
=> Name_Last
))))));
3285 Analyze_And_Resolve
(N
, Typ
);
3292 -- Transforms 'Fraction into a call to the floating-point attribute
3293 -- function Fraction in Fat_xxx (where xxx is the root type)
3295 when Attribute_Fraction
=>
3296 Expand_Fpt_Attribute_R
(N
);
3302 when Attribute_From_Any
=> From_Any
: declare
3303 P_Type
: constant Entity_Id
:= Etype
(Pref
);
3304 Decls
: constant List_Id
:= New_List
;
3307 Build_From_Any_Call
(P_Type
,
3308 Relocate_Node
(First
(Exprs
)),
3310 Insert_Actions
(N
, Decls
);
3311 Analyze_And_Resolve
(N
, P_Type
);
3314 ----------------------
3315 -- Has_Same_Storage --
3316 ----------------------
3318 when Attribute_Has_Same_Storage
=> Has_Same_Storage
: declare
3319 Loc
: constant Source_Ptr
:= Sloc
(N
);
3321 X
: constant Node_Id
:= Prefix
(N
);
3322 Y
: constant Node_Id
:= First
(Expressions
(N
));
3325 X_Addr
, Y_Addr
: Node_Id
;
3326 -- Rhe expressions for their addresses
3328 X_Size
, Y_Size
: Node_Id
;
3329 -- Rhe expressions for their sizes
3332 -- The attribute is expanded as:
3334 -- (X'address = Y'address)
3335 -- and then (X'Size = Y'Size)
3337 -- If both arguments have the same Etype the second conjunct can be
3341 Make_Attribute_Reference
(Loc
,
3342 Attribute_Name
=> Name_Address
,
3343 Prefix
=> New_Copy_Tree
(X
));
3346 Make_Attribute_Reference
(Loc
,
3347 Attribute_Name
=> Name_Address
,
3348 Prefix
=> New_Copy_Tree
(Y
));
3351 Make_Attribute_Reference
(Loc
,
3352 Attribute_Name
=> Name_Size
,
3353 Prefix
=> New_Copy_Tree
(X
));
3356 Make_Attribute_Reference
(Loc
,
3357 Attribute_Name
=> Name_Size
,
3358 Prefix
=> New_Copy_Tree
(Y
));
3360 if Etype
(X
) = Etype
(Y
) then
3363 Left_Opnd
=> X_Addr
,
3364 Right_Opnd
=> Y_Addr
)));
3370 Left_Opnd
=> X_Addr
,
3371 Right_Opnd
=> Y_Addr
),
3374 Left_Opnd
=> X_Size
,
3375 Right_Opnd
=> Y_Size
)));
3378 Analyze_And_Resolve
(N
, Standard_Boolean
);
3379 end Has_Same_Storage
;
3385 -- For an exception returns a reference to the exception data:
3386 -- Exception_Id!(Prefix'Reference)
3388 -- For a task it returns a reference to the _task_id component of
3389 -- corresponding record:
3391 -- taskV!(Prefix)._Task_Id, converted to the type Task_Id defined
3393 -- in Ada.Task_Identification
3395 when Attribute_Identity
=> Identity
: declare
3396 Id_Kind
: Entity_Id
;
3399 if Ptyp
= Standard_Exception_Type
then
3400 Id_Kind
:= RTE
(RE_Exception_Id
);
3402 if Present
(Renamed_Object
(Entity
(Pref
))) then
3403 Set_Entity
(Pref
, Renamed_Object
(Entity
(Pref
)));
3407 Unchecked_Convert_To
(Id_Kind
, Make_Reference
(Loc
, Pref
)));
3409 Id_Kind
:= RTE
(RO_AT_Task_Id
);
3411 -- If the prefix is a task interface, the Task_Id is obtained
3412 -- dynamically through a dispatching call, as for other task
3413 -- attributes applied to interfaces.
3415 if Ada_Version
>= Ada_2005
3416 and then Ekind
(Ptyp
) = E_Class_Wide_Type
3417 and then Is_Interface
(Ptyp
)
3418 and then Is_Task_Interface
(Ptyp
)
3421 Unchecked_Convert_To
(Id_Kind
,
3422 Make_Selected_Component
(Loc
,
3424 New_Copy_Tree
(Pref
),
3426 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
))));
3430 Unchecked_Convert_To
(Id_Kind
, Concurrent_Ref
(Pref
)));
3434 Analyze_And_Resolve
(N
, Id_Kind
);
3441 -- Image attribute is handled in separate unit Exp_Imgv
3443 when Attribute_Image
=>
3444 Exp_Imgv
.Expand_Image_Attribute
(N
);
3450 -- X'Img is expanded to typ'Image (X), where typ is the type of X
3452 when Attribute_Img
=> Img
:
3455 Make_Attribute_Reference
(Loc
,
3456 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
3457 Attribute_Name
=> Name_Image
,
3458 Expressions
=> New_List
(Relocate_Node
(Pref
))));
3460 Analyze_And_Resolve
(N
, Standard_String
);
3467 when Attribute_Input
=> Input
: declare
3468 P_Type
: constant Entity_Id
:= Entity
(Pref
);
3469 B_Type
: constant Entity_Id
:= Base_Type
(P_Type
);
3470 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
3471 Strm
: constant Node_Id
:= First
(Exprs
);
3479 Cntrl
: Node_Id
:= Empty
;
3480 -- Value for controlling argument in call. Always Empty except in
3481 -- the dispatching (class-wide type) case, where it is a reference
3482 -- to the dummy object initialized to the right internal tag.
3484 procedure Freeze_Stream_Subprogram
(F
: Entity_Id
);
3485 -- The expansion of the attribute reference may generate a call to
3486 -- a user-defined stream subprogram that is frozen by the call. This
3487 -- can lead to access-before-elaboration problem if the reference
3488 -- appears in an object declaration and the subprogram body has not
3489 -- been seen. The freezing of the subprogram requires special code
3490 -- because it appears in an expanded context where expressions do
3491 -- not freeze their constituents.
3493 ------------------------------
3494 -- Freeze_Stream_Subprogram --
3495 ------------------------------
3497 procedure Freeze_Stream_Subprogram
(F
: Entity_Id
) is
3498 Decl
: constant Node_Id
:= Unit_Declaration_Node
(F
);
3502 -- If this is user-defined subprogram, the corresponding
3503 -- stream function appears as a renaming-as-body, and the
3504 -- user subprogram must be retrieved by tree traversal.
3507 and then Nkind
(Decl
) = N_Subprogram_Declaration
3508 and then Present
(Corresponding_Body
(Decl
))
3510 Bod
:= Corresponding_Body
(Decl
);
3512 if Nkind
(Unit_Declaration_Node
(Bod
)) =
3513 N_Subprogram_Renaming_Declaration
3515 Set_Is_Frozen
(Entity
(Name
(Unit_Declaration_Node
(Bod
))));
3518 end Freeze_Stream_Subprogram
;
3520 -- Start of processing for Input
3523 -- If no underlying type, we have an error that will be diagnosed
3524 -- elsewhere, so here we just completely ignore the expansion.
3530 -- Stream operations can appear in user code even if the restriction
3531 -- No_Streams is active (for example, when instantiating a predefined
3532 -- container). In that case rewrite the attribute as a Raise to
3533 -- prevent any run-time use.
3535 if Restriction_Active
(No_Streams
) then
3537 Make_Raise_Program_Error
(Sloc
(N
),
3538 Reason
=> PE_Stream_Operation_Not_Allowed
));
3539 Set_Etype
(N
, B_Type
);
3543 -- If there is a TSS for Input, just call it
3545 Fname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Input
);
3547 if Present
(Fname
) then
3551 -- If there is a Stream_Convert pragma, use it, we rewrite
3553 -- sourcetyp'Input (stream)
3557 -- sourcetyp (streamread (strmtyp'Input (stream)));
3559 -- where streamread is the given Read function that converts an
3560 -- argument of type strmtyp to type sourcetyp or a type from which
3561 -- it is derived (extra conversion required for the derived case).
3563 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
3565 if Present
(Prag
) then
3566 Arg2
:= Next
(First
(Pragma_Argument_Associations
(Prag
)));
3567 Rfunc
:= Entity
(Expression
(Arg2
));
3571 Make_Function_Call
(Loc
,
3572 Name
=> New_Occurrence_Of
(Rfunc
, Loc
),
3573 Parameter_Associations
=> New_List
(
3574 Make_Attribute_Reference
(Loc
,
3577 (Etype
(First_Formal
(Rfunc
)), Loc
),
3578 Attribute_Name
=> Name_Input
,
3579 Expressions
=> Exprs
)))));
3581 Analyze_And_Resolve
(N
, B_Type
);
3586 elsif Is_Elementary_Type
(U_Type
) then
3588 -- A special case arises if we have a defined _Read routine,
3589 -- since in this case we are required to call this routine.
3591 if Present
(TSS
(Base_Type
(U_Type
), TSS_Stream_Read
)) then
3592 Build_Record_Or_Elementary_Input_Function
3593 (Loc
, U_Type
, Decl
, Fname
);
3594 Insert_Action
(N
, Decl
);
3596 -- For normal cases, we call the I_xxx routine directly
3599 Rewrite
(N
, Build_Elementary_Input_Call
(N
));
3600 Analyze_And_Resolve
(N
, P_Type
);
3606 elsif Is_Array_Type
(U_Type
) then
3607 Build_Array_Input_Function
(Loc
, U_Type
, Decl
, Fname
);
3608 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
3610 -- Dispatching case with class-wide type
3612 elsif Is_Class_Wide_Type
(P_Type
) then
3614 -- No need to do anything else compiling under restriction
3615 -- No_Dispatching_Calls. During the semantic analysis we
3616 -- already notified such violation.
3618 if Restriction_Active
(No_Dispatching_Calls
) then
3623 Rtyp
: constant Entity_Id
:= Root_Type
(P_Type
);
3629 -- Read the internal tag (RM 13.13.2(34)) and use it to
3630 -- initialize a dummy tag object:
3632 -- Dnn : Ada.Tags.Tag :=
3633 -- Descendant_Tag (String'Input (Strm), P_Type);
3635 -- This dummy object is used only to provide a controlling
3636 -- argument for the eventual _Input call. Descendant_Tag is
3637 -- called rather than Internal_Tag to ensure that we have a
3638 -- tag for a type that is descended from the prefix type and
3639 -- declared at the same accessibility level (the exception
3640 -- Tag_Error will be raised otherwise). The level check is
3641 -- required for Ada 2005 because tagged types can be
3642 -- extended in nested scopes (AI-344).
3645 Make_Function_Call
(Loc
,
3647 New_Occurrence_Of
(RTE
(RE_Descendant_Tag
), Loc
),
3648 Parameter_Associations
=> New_List
(
3649 Make_Attribute_Reference
(Loc
,
3650 Prefix
=> New_Occurrence_Of
(Standard_String
, Loc
),
3651 Attribute_Name
=> Name_Input
,
3652 Expressions
=> New_List
(
3653 Relocate_Node
(Duplicate_Subexpr
(Strm
)))),
3654 Make_Attribute_Reference
(Loc
,
3655 Prefix
=> New_Occurrence_Of
(P_Type
, Loc
),
3656 Attribute_Name
=> Name_Tag
)));
3658 Dnn
:= Make_Temporary
(Loc
, 'D', Expr
);
3661 Make_Object_Declaration
(Loc
,
3662 Defining_Identifier
=> Dnn
,
3663 Object_Definition
=>
3664 New_Occurrence_Of
(RTE
(RE_Tag
), Loc
),
3665 Expression
=> Expr
);
3667 Insert_Action
(N
, Decl
);
3669 -- Now we need to get the entity for the call, and construct
3670 -- a function call node, where we preset a reference to Dnn
3671 -- as the controlling argument (doing an unchecked convert
3672 -- to the class-wide tagged type to make it look like a real
3675 Fname
:= Find_Prim_Op
(Rtyp
, TSS_Stream_Input
);
3677 Unchecked_Convert_To
(P_Type
,
3678 New_Occurrence_Of
(Dnn
, Loc
));
3679 Set_Etype
(Cntrl
, P_Type
);
3680 Set_Parent
(Cntrl
, N
);
3683 -- For tagged types, use the primitive Input function
3685 elsif Is_Tagged_Type
(U_Type
) then
3686 Fname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Input
);
3688 -- All other record type cases, including protected records. The
3689 -- latter only arise for expander generated code for handling
3690 -- shared passive partition access.
3694 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
3696 -- Ada 2005 (AI-216): Program_Error is raised executing default
3697 -- implementation of the Input attribute of an unchecked union
3698 -- type if the type lacks default discriminant values.
3700 if Is_Unchecked_Union
(Base_Type
(U_Type
))
3701 and then No
(Discriminant_Constraint
(U_Type
))
3704 Make_Raise_Program_Error
(Loc
,
3705 Reason
=> PE_Unchecked_Union_Restriction
));
3710 -- Build the type's Input function, passing the subtype rather
3711 -- than its base type, because checks are needed in the case of
3712 -- constrained discriminants (see Ada 2012 AI05-0192).
3714 Build_Record_Or_Elementary_Input_Function
3715 (Loc
, U_Type
, Decl
, Fname
);
3716 Insert_Action
(N
, Decl
);
3718 if Nkind
(Parent
(N
)) = N_Object_Declaration
3719 and then Is_Record_Type
(U_Type
)
3721 -- The stream function may contain calls to user-defined
3722 -- Read procedures for individual components.
3729 Comp
:= First_Component
(U_Type
);
3730 while Present
(Comp
) loop
3732 Find_Stream_Subprogram
3733 (Etype
(Comp
), TSS_Stream_Read
);
3735 if Present
(Func
) then
3736 Freeze_Stream_Subprogram
(Func
);
3739 Next_Component
(Comp
);
3746 -- If we fall through, Fname is the function to be called. The result
3747 -- is obtained by calling the appropriate function, then converting
3748 -- the result. The conversion does a subtype check.
3751 Make_Function_Call
(Loc
,
3752 Name
=> New_Occurrence_Of
(Fname
, Loc
),
3753 Parameter_Associations
=> New_List
(
3754 Relocate_Node
(Strm
)));
3756 Set_Controlling_Argument
(Call
, Cntrl
);
3757 Rewrite
(N
, Unchecked_Convert_To
(P_Type
, Call
));
3758 Analyze_And_Resolve
(N
, P_Type
);
3760 if Nkind
(Parent
(N
)) = N_Object_Declaration
then
3761 Freeze_Stream_Subprogram
(Fname
);
3771 -- inttype'Fixed_Value (fixed-value)
3775 -- inttype(integer-value))
3777 -- we do all the required analysis of the conversion here, because we do
3778 -- not want this to go through the fixed-point conversion circuits. Note
3779 -- that the back end always treats fixed-point as equivalent to the
3780 -- corresponding integer type anyway.
3782 when Attribute_Integer_Value
=> Integer_Value
:
3785 Make_Type_Conversion
(Loc
,
3786 Subtype_Mark
=> New_Occurrence_Of
(Entity
(Pref
), Loc
),
3787 Expression
=> Relocate_Node
(First
(Exprs
))));
3788 Set_Etype
(N
, Entity
(Pref
));
3791 -- Note: it might appear that a properly analyzed unchecked conversion
3792 -- would be just fine here, but that's not the case, since the full
3793 -- range checks performed by the following call are critical.
3795 Apply_Type_Conversion_Checks
(N
);
3802 when Attribute_Invalid_Value
=>
3803 Rewrite
(N
, Get_Simple_Init_Val
(Ptyp
, N
));
3809 when Attribute_Last
=>
3811 -- If the prefix type is a constrained packed array type which
3812 -- already has a Packed_Array_Impl_Type representation defined, then
3813 -- replace this attribute with a direct reference to 'Last of the
3814 -- appropriate index subtype (since otherwise the back end will try
3815 -- to give us the value of 'Last for this implementation type).
3817 if Is_Constrained_Packed_Array
(Ptyp
) then
3819 Make_Attribute_Reference
(Loc
,
3820 Attribute_Name
=> Name_Last
,
3821 Prefix
=> New_Occurrence_Of
(Get_Index_Subtype
(N
), Loc
)));
3822 Analyze_And_Resolve
(N
, Typ
);
3824 -- For access type, apply access check as needed
3826 elsif Is_Access_Type
(Ptyp
) then
3827 Apply_Access_Check
(N
);
3829 -- For scalar type, if low bound is a reference to an entity, just
3830 -- replace with a direct reference. Note that we can only have a
3831 -- reference to a constant entity at this stage, anything else would
3832 -- have already been rewritten.
3834 elsif Is_Scalar_Type
(Ptyp
) then
3836 Hi
: constant Node_Id
:= Type_High_Bound
(Ptyp
);
3838 if Is_Entity_Name
(Hi
) then
3839 Rewrite
(N
, New_Occurrence_Of
(Entity
(Hi
), Loc
));
3848 -- We compute this if a component clause was present, otherwise we leave
3849 -- the computation up to the back end, since we don't know what layout
3852 when Attribute_Last_Bit
=> Last_Bit_Attr
: declare
3853 CE
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
3856 -- In Ada 2005 (or later) if we have the non-default bit order, then
3857 -- we return the original value as given in the component clause
3858 -- (RM 2005 13.5.2(3/2)).
3860 if Present
(Component_Clause
(CE
))
3861 and then Ada_Version
>= Ada_2005
3862 and then Reverse_Bit_Order
(Scope
(CE
))
3865 Make_Integer_Literal
(Loc
,
3866 Intval
=> Expr_Value
(Last_Bit
(Component_Clause
(CE
)))));
3867 Analyze_And_Resolve
(N
, Typ
);
3869 -- Otherwise (Ada 83/95 or Ada 2005 or later with default bit order),
3870 -- rewrite with normalized value if we know it statically.
3872 elsif Known_Static_Component_Bit_Offset
(CE
)
3873 and then Known_Static_Esize
(CE
)
3876 Make_Integer_Literal
(Loc
,
3877 Intval
=> (Component_Bit_Offset
(CE
) mod System_Storage_Unit
)
3879 Analyze_And_Resolve
(N
, Typ
);
3881 -- Otherwise leave to back end, just apply universal integer checks
3884 Apply_Universal_Integer_Attribute_Checks
(N
);
3892 -- Transforms 'Leading_Part into a call to the floating-point attribute
3893 -- function Leading_Part in Fat_xxx (where xxx is the root type)
3895 -- Note: strictly, we should generate special case code to deal with
3896 -- absurdly large positive arguments (greater than Integer'Last), which
3897 -- result in returning the first argument unchanged, but it hardly seems
3898 -- worth the effort. We raise constraint error for absurdly negative
3899 -- arguments which is fine.
3901 when Attribute_Leading_Part
=>
3902 Expand_Fpt_Attribute_RI
(N
);
3908 when Attribute_Length
=> Length
: declare
3913 -- Processing for packed array types
3915 if Is_Array_Type
(Ptyp
) and then Is_Packed
(Ptyp
) then
3916 Ityp
:= Get_Index_Subtype
(N
);
3918 -- If the index type, Ityp, is an enumeration type with holes,
3919 -- then we calculate X'Length explicitly using
3922 -- (0, Ityp'Pos (X'Last (N)) -
3923 -- Ityp'Pos (X'First (N)) + 1);
3925 -- Since the bounds in the template are the representation values
3926 -- and the back end would get the wrong value.
3928 if Is_Enumeration_Type
(Ityp
)
3929 and then Present
(Enum_Pos_To_Rep
(Base_Type
(Ityp
)))
3934 Xnum
:= Expr_Value
(First
(Expressions
(N
)));
3938 Make_Attribute_Reference
(Loc
,
3939 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
3940 Attribute_Name
=> Name_Max
,
3941 Expressions
=> New_List
3942 (Make_Integer_Literal
(Loc
, 0),
3946 Make_Op_Subtract
(Loc
,
3948 Make_Attribute_Reference
(Loc
,
3949 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
3950 Attribute_Name
=> Name_Pos
,
3952 Expressions
=> New_List
(
3953 Make_Attribute_Reference
(Loc
,
3954 Prefix
=> Duplicate_Subexpr
(Pref
),
3955 Attribute_Name
=> Name_Last
,
3956 Expressions
=> New_List
(
3957 Make_Integer_Literal
(Loc
, Xnum
))))),
3960 Make_Attribute_Reference
(Loc
,
3961 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
3962 Attribute_Name
=> Name_Pos
,
3964 Expressions
=> New_List
(
3965 Make_Attribute_Reference
(Loc
,
3967 Duplicate_Subexpr_No_Checks
(Pref
),
3968 Attribute_Name
=> Name_First
,
3969 Expressions
=> New_List
(
3970 Make_Integer_Literal
(Loc
, Xnum
)))))),
3972 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)))));
3974 Analyze_And_Resolve
(N
, Typ
, Suppress
=> All_Checks
);
3977 -- If the prefix type is a constrained packed array type which
3978 -- already has a Packed_Array_Impl_Type representation defined,
3979 -- then replace this attribute with a reference to 'Range_Length
3980 -- of the appropriate index subtype (since otherwise the
3981 -- back end will try to give us the value of 'Length for
3982 -- this implementation type).s
3984 elsif Is_Constrained
(Ptyp
) then
3986 Make_Attribute_Reference
(Loc
,
3987 Attribute_Name
=> Name_Range_Length
,
3988 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
)));
3989 Analyze_And_Resolve
(N
, Typ
);
3994 elsif Is_Access_Type
(Ptyp
) then
3995 Apply_Access_Check
(N
);
3997 -- If the designated type is a packed array type, then we convert
3998 -- the reference to:
4001 -- xtyp'Pos (Pref'Last (Expr)) -
4002 -- xtyp'Pos (Pref'First (Expr)));
4004 -- This is a bit complex, but it is the easiest thing to do that
4005 -- works in all cases including enum types with holes xtyp here
4006 -- is the appropriate index type.
4009 Dtyp
: constant Entity_Id
:= Designated_Type
(Ptyp
);
4013 if Is_Array_Type
(Dtyp
) and then Is_Packed
(Dtyp
) then
4014 Xtyp
:= Get_Index_Subtype
(N
);
4017 Make_Attribute_Reference
(Loc
,
4018 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
4019 Attribute_Name
=> Name_Max
,
4020 Expressions
=> New_List
(
4021 Make_Integer_Literal
(Loc
, 0),
4024 Make_Integer_Literal
(Loc
, 1),
4025 Make_Op_Subtract
(Loc
,
4027 Make_Attribute_Reference
(Loc
,
4028 Prefix
=> New_Occurrence_Of
(Xtyp
, Loc
),
4029 Attribute_Name
=> Name_Pos
,
4030 Expressions
=> New_List
(
4031 Make_Attribute_Reference
(Loc
,
4032 Prefix
=> Duplicate_Subexpr
(Pref
),
4033 Attribute_Name
=> Name_Last
,
4035 New_Copy_List
(Exprs
)))),
4038 Make_Attribute_Reference
(Loc
,
4039 Prefix
=> New_Occurrence_Of
(Xtyp
, Loc
),
4040 Attribute_Name
=> Name_Pos
,
4041 Expressions
=> New_List
(
4042 Make_Attribute_Reference
(Loc
,
4044 Duplicate_Subexpr_No_Checks
(Pref
),
4045 Attribute_Name
=> Name_First
,
4047 New_Copy_List
(Exprs
)))))))));
4049 Analyze_And_Resolve
(N
, Typ
);
4053 -- Otherwise leave it to the back end
4056 Apply_Universal_Integer_Attribute_Checks
(N
);
4060 -- Attribute Loop_Entry is replaced with a reference to a constant value
4061 -- which captures the prefix at the entry point of the related loop. The
4062 -- loop itself may be transformed into a conditional block.
4064 when Attribute_Loop_Entry
=>
4065 Expand_Loop_Entry_Attribute
(N
);
4071 -- Transforms 'Machine into a call to the floating-point attribute
4072 -- function Machine in Fat_xxx (where xxx is the root type).
4073 -- Expansion is avoided for cases the back end can handle directly.
4075 when Attribute_Machine
=>
4076 if not Is_Inline_Floating_Point_Attribute
(N
) then
4077 Expand_Fpt_Attribute_R
(N
);
4080 ----------------------
4081 -- Machine_Rounding --
4082 ----------------------
4084 -- Transforms 'Machine_Rounding into a call to the floating-point
4085 -- attribute function Machine_Rounding in Fat_xxx (where xxx is the root
4086 -- type). Expansion is avoided for cases the back end can handle
4089 when Attribute_Machine_Rounding
=>
4090 if not Is_Inline_Floating_Point_Attribute
(N
) then
4091 Expand_Fpt_Attribute_R
(N
);
4098 -- Machine_Size is equivalent to Object_Size, so transform it into
4099 -- Object_Size and that way the back end never sees Machine_Size.
4101 when Attribute_Machine_Size
=>
4103 Make_Attribute_Reference
(Loc
,
4104 Prefix
=> Prefix
(N
),
4105 Attribute_Name
=> Name_Object_Size
));
4107 Analyze_And_Resolve
(N
, Typ
);
4113 -- The only case that can get this far is the dynamic case of the old
4114 -- Ada 83 Mantissa attribute for the fixed-point case. For this case,
4121 -- ityp (System.Mantissa.Mantissa_Value
4122 -- (Integer'Integer_Value (typ'First),
4123 -- Integer'Integer_Value (typ'Last)));
4125 when Attribute_Mantissa
=> Mantissa
: begin
4128 Make_Function_Call
(Loc
,
4129 Name
=> New_Occurrence_Of
(RTE
(RE_Mantissa_Value
), Loc
),
4131 Parameter_Associations
=> New_List
(
4133 Make_Attribute_Reference
(Loc
,
4134 Prefix
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
4135 Attribute_Name
=> Name_Integer_Value
,
4136 Expressions
=> New_List
(
4138 Make_Attribute_Reference
(Loc
,
4139 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
4140 Attribute_Name
=> Name_First
))),
4142 Make_Attribute_Reference
(Loc
,
4143 Prefix
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
4144 Attribute_Name
=> Name_Integer_Value
,
4145 Expressions
=> New_List
(
4147 Make_Attribute_Reference
(Loc
,
4148 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
4149 Attribute_Name
=> Name_Last
)))))));
4151 Analyze_And_Resolve
(N
, Typ
);
4158 when Attribute_Max
=>
4159 Expand_Min_Max_Attribute
(N
);
4161 ----------------------------------
4162 -- Max_Size_In_Storage_Elements --
4163 ----------------------------------
4165 when Attribute_Max_Size_In_Storage_Elements
=> declare
4166 Typ
: constant Entity_Id
:= Etype
(N
);
4169 Conversion_Added
: Boolean := False;
4170 -- A flag which tracks whether the original attribute has been
4171 -- wrapped inside a type conversion.
4174 Apply_Universal_Integer_Attribute_Checks
(N
);
4176 -- The universal integer check may sometimes add a type conversion,
4177 -- retrieve the original attribute reference from the expression.
4180 if Nkind
(Attr
) = N_Type_Conversion
then
4181 Attr
:= Expression
(Attr
);
4182 Conversion_Added
:= True;
4185 -- Heap-allocated controlled objects contain two extra pointers which
4186 -- are not part of the actual type. Transform the attribute reference
4187 -- into a runtime expression to add the size of the hidden header.
4189 -- Do not perform this expansion on .NET/JVM targets because the
4190 -- two pointers are already present in the type.
4192 if VM_Target
= No_VM
4193 and then Nkind
(Attr
) = N_Attribute_Reference
4194 and then Needs_Finalization
(Ptyp
)
4195 and then not Header_Size_Added
(Attr
)
4197 Set_Header_Size_Added
(Attr
);
4200 -- P'Max_Size_In_Storage_Elements +
4201 -- Universal_Integer
4202 -- (Header_Size_With_Padding (Ptyp'Alignment))
4206 Left_Opnd
=> Relocate_Node
(Attr
),
4208 Convert_To
(Universal_Integer
,
4209 Make_Function_Call
(Loc
,
4212 (RTE
(RE_Header_Size_With_Padding
), Loc
),
4214 Parameter_Associations
=> New_List
(
4215 Make_Attribute_Reference
(Loc
,
4217 New_Occurrence_Of
(Ptyp
, Loc
),
4218 Attribute_Name
=> Name_Alignment
))))));
4220 -- Add a conversion to the target type
4222 if not Conversion_Added
then
4224 Make_Type_Conversion
(Loc
,
4225 Subtype_Mark
=> New_Occurrence_Of
(Typ
, Loc
),
4226 Expression
=> Relocate_Node
(Attr
)));
4234 --------------------
4235 -- Mechanism_Code --
4236 --------------------
4238 when Attribute_Mechanism_Code
=>
4240 -- We must replace the prefix i the renamed case
4242 if Is_Entity_Name
(Pref
)
4243 and then Present
(Alias
(Entity
(Pref
)))
4245 Set_Renamed_Subprogram
(Pref
, Alias
(Entity
(Pref
)));
4252 when Attribute_Min
=>
4253 Expand_Min_Max_Attribute
(N
);
4259 when Attribute_Mod
=> Mod_Case
: declare
4260 Arg
: constant Node_Id
:= Relocate_Node
(First
(Exprs
));
4261 Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Arg
));
4262 Modv
: constant Uint
:= Modulus
(Btyp
);
4266 -- This is not so simple. The issue is what type to use for the
4267 -- computation of the modular value.
4269 -- The easy case is when the modulus value is within the bounds
4270 -- of the signed integer type of the argument. In this case we can
4271 -- just do the computation in that signed integer type, and then
4272 -- do an ordinary conversion to the target type.
4274 if Modv
<= Expr_Value
(Hi
) then
4279 Right_Opnd
=> Make_Integer_Literal
(Loc
, Modv
))));
4281 -- Here we know that the modulus is larger than type'Last of the
4282 -- integer type. There are two cases to consider:
4284 -- a) The integer value is non-negative. In this case, it is
4285 -- returned as the result (since it is less than the modulus).
4287 -- b) The integer value is negative. In this case, we know that the
4288 -- result is modulus + value, where the value might be as small as
4289 -- -modulus. The trouble is what type do we use to do the subtract.
4290 -- No type will do, since modulus can be as big as 2**64, and no
4291 -- integer type accommodates this value. Let's do bit of algebra
4294 -- = modulus - (-value)
4295 -- = (modulus - 1) - (-value - 1)
4297 -- Now modulus - 1 is certainly in range of the modular type.
4298 -- -value is in the range 1 .. modulus, so -value -1 is in the
4299 -- range 0 .. modulus-1 which is in range of the modular type.
4300 -- Furthermore, (-value - 1) can be expressed as -(value + 1)
4301 -- which we can compute using the integer base type.
4303 -- Once this is done we analyze the if expression without range
4304 -- checks, because we know everything is in range, and we want
4305 -- to prevent spurious warnings on either branch.
4309 Make_If_Expression
(Loc
,
4310 Expressions
=> New_List
(
4312 Left_Opnd
=> Duplicate_Subexpr
(Arg
),
4313 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
4316 Duplicate_Subexpr_No_Checks
(Arg
)),
4318 Make_Op_Subtract
(Loc
,
4320 Make_Integer_Literal
(Loc
,
4321 Intval
=> Modv
- 1),
4327 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Arg
),
4329 Make_Integer_Literal
(Loc
,
4330 Intval
=> 1))))))));
4334 Analyze_And_Resolve
(N
, Btyp
, Suppress
=> All_Checks
);
4341 -- Transforms 'Model into a call to the floating-point attribute
4342 -- function Model in Fat_xxx (where xxx is the root type).
4343 -- Expansion is avoided for cases the back end can handle directly.
4345 when Attribute_Model
=>
4346 if not Is_Inline_Floating_Point_Attribute
(N
) then
4347 Expand_Fpt_Attribute_R
(N
);
4354 -- The processing for Object_Size shares the processing for Size
4360 when Attribute_Old
=> Old
: declare
4366 Temp
:= Make_Temporary
(Loc
, 'T', Pref
);
4368 -- Set the entity kind now in order to mark the temporary as a
4369 -- handler of attribute 'Old's prefix.
4371 Set_Ekind
(Temp
, E_Constant
);
4372 Set_Stores_Attribute_Old_Prefix
(Temp
);
4374 -- Climb the parent chain looking for subprogram _Postconditions
4377 while Present
(Subp
) loop
4378 exit when Nkind
(Subp
) = N_Subprogram_Body
4379 and then Chars
(Defining_Entity
(Subp
)) = Name_uPostconditions
;
4381 -- If assertions are disabled, no need to create the declaration
4382 -- that preserves the value. The postcondition pragma in which
4383 -- 'Old appears will be checked or disabled according to the
4384 -- current policy in effect.
4386 if Nkind
(Subp
) = N_Pragma
and then not Is_Checked
(Subp
) then
4390 Subp
:= Parent
(Subp
);
4393 -- 'Old can only appear in a postcondition, the generated body of
4394 -- _Postconditions must be in the tree.
4396 pragma Assert
(Present
(Subp
));
4399 -- Temp : constant <Pref type> := <Pref>;
4402 Make_Object_Declaration
(Loc
,
4403 Defining_Identifier
=> Temp
,
4404 Constant_Present
=> True,
4405 Object_Definition
=> New_Occurrence_Of
(Etype
(N
), Loc
),
4406 Expression
=> Pref
);
4408 -- Push the scope of the related subprogram where _Postcondition
4409 -- resides as this ensures that the object will be analyzed in the
4412 Push_Scope
(Scope
(Defining_Entity
(Subp
)));
4414 -- The object declaration is inserted before the body of subprogram
4415 -- _Postconditions. This ensures that any precondition-like actions
4416 -- are still executed before any parameter values are captured and
4417 -- the multiple 'Old occurrences appear in order of declaration.
4419 Insert_Before_And_Analyze
(Subp
, Asn_Stm
);
4422 -- Ensure that the prefix of attribute 'Old is valid. The check must
4423 -- be inserted after the expansion of the attribute has taken place
4424 -- to reflect the new placement of the prefix.
4426 if Validity_Checks_On
and then Validity_Check_Operands
then
4427 Ensure_Valid
(Pref
);
4430 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
4433 ----------------------
4434 -- Overlaps_Storage --
4435 ----------------------
4437 when Attribute_Overlaps_Storage
=> Overlaps_Storage
: declare
4438 Loc
: constant Source_Ptr
:= Sloc
(N
);
4440 X
: constant Node_Id
:= Prefix
(N
);
4441 Y
: constant Node_Id
:= First
(Expressions
(N
));
4444 X_Addr
, Y_Addr
: Node_Id
;
4445 -- the expressions for their integer addresses
4447 X_Size
, Y_Size
: Node_Id
;
4448 -- the expressions for their sizes
4453 -- Attribute expands into:
4455 -- if X'Address < Y'address then
4456 -- (X'address + X'Size - 1) >= Y'address
4458 -- (Y'address + Y'size - 1) >= X'Address
4461 -- with the proper address operations. We convert addresses to
4462 -- integer addresses to use predefined arithmetic. The size is
4463 -- expressed in storage units.
4466 Unchecked_Convert_To
(RTE
(RE_Integer_Address
),
4467 Make_Attribute_Reference
(Loc
,
4468 Attribute_Name
=> Name_Address
,
4469 Prefix
=> New_Copy_Tree
(X
)));
4472 Unchecked_Convert_To
(RTE
(RE_Integer_Address
),
4473 Make_Attribute_Reference
(Loc
,
4474 Attribute_Name
=> Name_Address
,
4475 Prefix
=> New_Copy_Tree
(Y
)));
4478 Make_Op_Divide
(Loc
,
4480 Make_Attribute_Reference
(Loc
,
4481 Attribute_Name
=> Name_Size
,
4482 Prefix
=> New_Copy_Tree
(X
)),
4484 Make_Integer_Literal
(Loc
, System_Storage_Unit
));
4487 Make_Op_Divide
(Loc
,
4489 Make_Attribute_Reference
(Loc
,
4490 Attribute_Name
=> Name_Size
,
4491 Prefix
=> New_Copy_Tree
(Y
)),
4493 Make_Integer_Literal
(Loc
, System_Storage_Unit
));
4497 Left_Opnd
=> X_Addr
,
4498 Right_Opnd
=> Y_Addr
);
4501 Make_If_Expression
(Loc
,
4508 Left_Opnd
=> X_Addr
,
4510 Make_Op_Subtract
(Loc
,
4511 Left_Opnd
=> X_Size
,
4512 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))),
4513 Right_Opnd
=> Y_Addr
),
4517 Left_Opnd
=> Y_Addr
,
4519 Make_Op_Subtract
(Loc
,
4520 Left_Opnd
=> Y_Size
,
4521 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))),
4522 Right_Opnd
=> X_Addr
))));
4524 Analyze_And_Resolve
(N
, Standard_Boolean
);
4525 end Overlaps_Storage
;
4531 when Attribute_Output
=> Output
: declare
4532 P_Type
: constant Entity_Id
:= Entity
(Pref
);
4533 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
4541 -- If no underlying type, we have an error that will be diagnosed
4542 -- elsewhere, so here we just completely ignore the expansion.
4548 -- Stream operations can appear in user code even if the restriction
4549 -- No_Streams is active (for example, when instantiating a predefined
4550 -- container). In that case rewrite the attribute as a Raise to
4551 -- prevent any run-time use.
4553 if Restriction_Active
(No_Streams
) then
4555 Make_Raise_Program_Error
(Sloc
(N
),
4556 Reason
=> PE_Stream_Operation_Not_Allowed
));
4557 Set_Etype
(N
, Standard_Void_Type
);
4561 -- If TSS for Output is present, just call it
4563 Pname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Output
);
4565 if Present
(Pname
) then
4569 -- If there is a Stream_Convert pragma, use it, we rewrite
4571 -- sourcetyp'Output (stream, Item)
4575 -- strmtyp'Output (Stream, strmwrite (acttyp (Item)));
4577 -- where strmwrite is the given Write function that converts an
4578 -- argument of type sourcetyp or a type acctyp, from which it is
4579 -- derived to type strmtyp. The conversion to acttyp is required
4580 -- for the derived case.
4582 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
4584 if Present
(Prag
) then
4586 Next
(Next
(First
(Pragma_Argument_Associations
(Prag
))));
4587 Wfunc
:= Entity
(Expression
(Arg3
));
4590 Make_Attribute_Reference
(Loc
,
4591 Prefix
=> New_Occurrence_Of
(Etype
(Wfunc
), Loc
),
4592 Attribute_Name
=> Name_Output
,
4593 Expressions
=> New_List
(
4594 Relocate_Node
(First
(Exprs
)),
4595 Make_Function_Call
(Loc
,
4596 Name
=> New_Occurrence_Of
(Wfunc
, Loc
),
4597 Parameter_Associations
=> New_List
(
4598 OK_Convert_To
(Etype
(First_Formal
(Wfunc
)),
4599 Relocate_Node
(Next
(First
(Exprs
)))))))));
4604 -- For elementary types, we call the W_xxx routine directly. Note
4605 -- that the effect of Write and Output is identical for the case
4606 -- of an elementary type (there are no discriminants or bounds).
4608 elsif Is_Elementary_Type
(U_Type
) then
4610 -- A special case arises if we have a defined _Write routine,
4611 -- since in this case we are required to call this routine.
4613 if Present
(TSS
(Base_Type
(U_Type
), TSS_Stream_Write
)) then
4614 Build_Record_Or_Elementary_Output_Procedure
4615 (Loc
, U_Type
, Decl
, Pname
);
4616 Insert_Action
(N
, Decl
);
4618 -- For normal cases, we call the W_xxx routine directly
4621 Rewrite
(N
, Build_Elementary_Write_Call
(N
));
4628 elsif Is_Array_Type
(U_Type
) then
4629 Build_Array_Output_Procedure
(Loc
, U_Type
, Decl
, Pname
);
4630 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
4632 -- Class-wide case, first output external tag, then dispatch
4633 -- to the appropriate primitive Output function (RM 13.13.2(31)).
4635 elsif Is_Class_Wide_Type
(P_Type
) then
4637 -- No need to do anything else compiling under restriction
4638 -- No_Dispatching_Calls. During the semantic analysis we
4639 -- already notified such violation.
4641 if Restriction_Active
(No_Dispatching_Calls
) then
4646 Strm
: constant Node_Id
:= First
(Exprs
);
4647 Item
: constant Node_Id
:= Next
(Strm
);
4650 -- Ada 2005 (AI-344): Check that the accessibility level
4651 -- of the type of the output object is not deeper than
4652 -- that of the attribute's prefix type.
4654 -- if Get_Access_Level (Item'Tag)
4655 -- /= Get_Access_Level (P_Type'Tag)
4660 -- String'Output (Strm, External_Tag (Item'Tag));
4662 -- We cannot figure out a practical way to implement this
4663 -- accessibility check on virtual machines, so we omit it.
4665 if Ada_Version
>= Ada_2005
4666 and then Tagged_Type_Expansion
4669 Make_Implicit_If_Statement
(N
,
4673 Build_Get_Access_Level
(Loc
,
4674 Make_Attribute_Reference
(Loc
,
4677 Duplicate_Subexpr
(Item
,
4679 Attribute_Name
=> Name_Tag
)),
4682 Make_Integer_Literal
(Loc
,
4683 Type_Access_Level
(P_Type
))),
4686 New_List
(Make_Raise_Statement
(Loc
,
4688 RTE
(RE_Tag_Error
), Loc
)))));
4692 Make_Attribute_Reference
(Loc
,
4693 Prefix
=> New_Occurrence_Of
(Standard_String
, Loc
),
4694 Attribute_Name
=> Name_Output
,
4695 Expressions
=> New_List
(
4696 Relocate_Node
(Duplicate_Subexpr
(Strm
)),
4697 Make_Function_Call
(Loc
,
4699 New_Occurrence_Of
(RTE
(RE_External_Tag
), Loc
),
4700 Parameter_Associations
=> New_List
(
4701 Make_Attribute_Reference
(Loc
,
4704 (Duplicate_Subexpr
(Item
, Name_Req
=> True)),
4705 Attribute_Name
=> Name_Tag
))))));
4708 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Output
);
4710 -- Tagged type case, use the primitive Output function
4712 elsif Is_Tagged_Type
(U_Type
) then
4713 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Output
);
4715 -- All other record type cases, including protected records.
4716 -- The latter only arise for expander generated code for
4717 -- handling shared passive partition access.
4721 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
4723 -- Ada 2005 (AI-216): Program_Error is raised when executing
4724 -- the default implementation of the Output attribute of an
4725 -- unchecked union type if the type lacks default discriminant
4728 if Is_Unchecked_Union
(Base_Type
(U_Type
))
4729 and then No
(Discriminant_Constraint
(U_Type
))
4732 Make_Raise_Program_Error
(Loc
,
4733 Reason
=> PE_Unchecked_Union_Restriction
));
4738 Build_Record_Or_Elementary_Output_Procedure
4739 (Loc
, Base_Type
(U_Type
), Decl
, Pname
);
4740 Insert_Action
(N
, Decl
);
4744 -- If we fall through, Pname is the name of the procedure to call
4746 Rewrite_Stream_Proc_Call
(Pname
);
4753 -- For enumeration types with a standard representation, Pos is
4754 -- handled by the back end.
4756 -- For enumeration types, with a non-standard representation we generate
4757 -- a call to the _Rep_To_Pos function created when the type was frozen.
4758 -- The call has the form
4760 -- _rep_to_pos (expr, flag)
4762 -- The parameter flag is True if range checks are enabled, causing
4763 -- Program_Error to be raised if the expression has an invalid
4764 -- representation, and False if range checks are suppressed.
4766 -- For integer types, Pos is equivalent to a simple integer
4767 -- conversion and we rewrite it as such
4769 when Attribute_Pos
=> Pos
:
4771 Etyp
: Entity_Id
:= Base_Type
(Entity
(Pref
));
4774 -- Deal with zero/non-zero boolean values
4776 if Is_Boolean_Type
(Etyp
) then
4777 Adjust_Condition
(First
(Exprs
));
4778 Etyp
:= Standard_Boolean
;
4779 Set_Prefix
(N
, New_Occurrence_Of
(Standard_Boolean
, Loc
));
4782 -- Case of enumeration type
4784 if Is_Enumeration_Type
(Etyp
) then
4786 -- Non-standard enumeration type (generate call)
4788 if Present
(Enum_Pos_To_Rep
(Etyp
)) then
4789 Append_To
(Exprs
, Rep_To_Pos_Flag
(Etyp
, Loc
));
4792 Make_Function_Call
(Loc
,
4794 New_Occurrence_Of
(TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
4795 Parameter_Associations
=> Exprs
)));
4797 Analyze_And_Resolve
(N
, Typ
);
4799 -- Standard enumeration type (do universal integer check)
4802 Apply_Universal_Integer_Attribute_Checks
(N
);
4805 -- Deal with integer types (replace by conversion)
4807 elsif Is_Integer_Type
(Etyp
) then
4808 Rewrite
(N
, Convert_To
(Typ
, First
(Exprs
)));
4809 Analyze_And_Resolve
(N
, Typ
);
4818 -- We compute this if a component clause was present, otherwise we leave
4819 -- the computation up to the back end, since we don't know what layout
4822 when Attribute_Position
=> Position_Attr
:
4824 CE
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
4827 if Present
(Component_Clause
(CE
)) then
4829 -- In Ada 2005 (or later) if we have the non-default bit order,
4830 -- then we return the original value as given in the component
4831 -- clause (RM 2005 13.5.2(2/2)).
4833 if Ada_Version
>= Ada_2005
4834 and then Reverse_Bit_Order
(Scope
(CE
))
4837 Make_Integer_Literal
(Loc
,
4838 Intval
=> Expr_Value
(Position
(Component_Clause
(CE
)))));
4840 -- Otherwise (Ada 83 or 95, or default bit order specified in
4841 -- later Ada version), return the normalized value.
4845 Make_Integer_Literal
(Loc
,
4846 Intval
=> Component_Bit_Offset
(CE
) / System_Storage_Unit
));
4849 Analyze_And_Resolve
(N
, Typ
);
4851 -- If back end is doing things, just apply universal integer checks
4854 Apply_Universal_Integer_Attribute_Checks
(N
);
4862 -- 1. Deal with enumeration types with holes.
4863 -- 2. For floating-point, generate call to attribute function.
4864 -- 3. For other cases, deal with constraint checking.
4866 when Attribute_Pred
=> Pred
:
4868 Etyp
: constant Entity_Id
:= Base_Type
(Ptyp
);
4872 -- For enumeration types with non-standard representations, we
4873 -- expand typ'Pred (x) into
4875 -- Pos_To_Rep (Rep_To_Pos (x) - 1)
4877 -- If the representation is contiguous, we compute instead
4878 -- Lit1 + Rep_to_Pos (x -1), to catch invalid representations.
4879 -- The conversion function Enum_Pos_To_Rep is defined on the
4880 -- base type, not the subtype, so we have to use the base type
4881 -- explicitly for this and other enumeration attributes.
4883 if Is_Enumeration_Type
(Ptyp
)
4884 and then Present
(Enum_Pos_To_Rep
(Etyp
))
4886 if Has_Contiguous_Rep
(Etyp
) then
4888 Unchecked_Convert_To
(Ptyp
,
4891 Make_Integer_Literal
(Loc
,
4892 Enumeration_Rep
(First_Literal
(Ptyp
))),
4894 Make_Function_Call
(Loc
,
4897 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
4899 Parameter_Associations
=>
4901 Unchecked_Convert_To
(Ptyp
,
4902 Make_Op_Subtract
(Loc
,
4904 Unchecked_Convert_To
(Standard_Integer
,
4905 Relocate_Node
(First
(Exprs
))),
4907 Make_Integer_Literal
(Loc
, 1))),
4908 Rep_To_Pos_Flag
(Ptyp
, Loc
))))));
4911 -- Add Boolean parameter True, to request program errror if
4912 -- we have a bad representation on our hands. If checks are
4913 -- suppressed, then add False instead
4915 Append_To
(Exprs
, Rep_To_Pos_Flag
(Ptyp
, Loc
));
4917 Make_Indexed_Component
(Loc
,
4920 (Enum_Pos_To_Rep
(Etyp
), Loc
),
4921 Expressions
=> New_List
(
4922 Make_Op_Subtract
(Loc
,
4924 Make_Function_Call
(Loc
,
4927 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
4928 Parameter_Associations
=> Exprs
),
4929 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)))));
4932 Analyze_And_Resolve
(N
, Typ
);
4934 -- For floating-point, we transform 'Pred into a call to the Pred
4935 -- floating-point attribute function in Fat_xxx (xxx is root type).
4936 -- Note that this function takes care of the overflow case.
4938 elsif Is_Floating_Point_Type
(Ptyp
) then
4939 Expand_Fpt_Attribute_R
(N
);
4940 Analyze_And_Resolve
(N
, Typ
);
4942 -- For modular types, nothing to do (no overflow, since wraps)
4944 elsif Is_Modular_Integer_Type
(Ptyp
) then
4947 -- For other types, if argument is marked as needing a range check or
4948 -- overflow checking is enabled, we must generate a check.
4950 elsif not Overflow_Checks_Suppressed
(Ptyp
)
4951 or else Do_Range_Check
(First
(Exprs
))
4953 Set_Do_Range_Check
(First
(Exprs
), False);
4954 Expand_Pred_Succ_Attribute
(N
);
4962 -- Ada 2005 (AI-327): Dynamic ceiling priorities
4964 -- We rewrite X'Priority as the following run-time call:
4966 -- Get_Ceiling (X._Object)
4968 -- Note that although X'Priority is notionally an object, it is quite
4969 -- deliberately not defined as an aliased object in the RM. This means
4970 -- that it works fine to rewrite it as a call, without having to worry
4971 -- about complications that would other arise from X'Priority'Access,
4972 -- which is illegal, because of the lack of aliasing.
4974 when Attribute_Priority
=>
4977 Conctyp
: Entity_Id
;
4978 Object_Parm
: Node_Id
;
4980 RT_Subprg_Name
: Node_Id
;
4983 -- Look for the enclosing concurrent type
4985 Conctyp
:= Current_Scope
;
4986 while not Is_Concurrent_Type
(Conctyp
) loop
4987 Conctyp
:= Scope
(Conctyp
);
4990 pragma Assert
(Is_Protected_Type
(Conctyp
));
4992 -- Generate the actual of the call
4994 Subprg
:= Current_Scope
;
4995 while not Present
(Protected_Body_Subprogram
(Subprg
)) loop
4996 Subprg
:= Scope
(Subprg
);
4999 -- Use of 'Priority inside protected entries and barriers (in
5000 -- both cases the type of the first formal of their expanded
5001 -- subprogram is Address)
5003 if Etype
(First_Entity
(Protected_Body_Subprogram
(Subprg
)))
5007 New_Itype
: Entity_Id
;
5010 -- In the expansion of protected entries the type of the
5011 -- first formal of the Protected_Body_Subprogram is an
5012 -- Address. In order to reference the _object component
5015 -- type T is access p__ptTV;
5018 New_Itype
:= Create_Itype
(E_Access_Type
, N
);
5019 Set_Etype
(New_Itype
, New_Itype
);
5020 Set_Directly_Designated_Type
(New_Itype
,
5021 Corresponding_Record_Type
(Conctyp
));
5022 Freeze_Itype
(New_Itype
, N
);
5025 -- T!(O)._object'unchecked_access
5028 Make_Attribute_Reference
(Loc
,
5030 Make_Selected_Component
(Loc
,
5032 Unchecked_Convert_To
(New_Itype
,
5035 (Protected_Body_Subprogram
(Subprg
)),
5038 Make_Identifier
(Loc
, Name_uObject
)),
5039 Attribute_Name
=> Name_Unchecked_Access
);
5042 -- Use of 'Priority inside a protected subprogram
5046 Make_Attribute_Reference
(Loc
,
5048 Make_Selected_Component
(Loc
,
5049 Prefix
=> New_Occurrence_Of
5051 (Protected_Body_Subprogram
(Subprg
)),
5053 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
5054 Attribute_Name
=> Name_Unchecked_Access
);
5057 -- Select the appropriate run-time subprogram
5059 if Number_Entries
(Conctyp
) = 0 then
5061 New_Occurrence_Of
(RTE
(RE_Get_Ceiling
), Loc
);
5064 New_Occurrence_Of
(RTE
(RO_PE_Get_Ceiling
), Loc
);
5068 Make_Function_Call
(Loc
,
5069 Name
=> RT_Subprg_Name
,
5070 Parameter_Associations
=> New_List
(Object_Parm
));
5074 -- Avoid the generation of extra checks on the pointer to the
5075 -- protected object.
5077 Analyze_And_Resolve
(N
, Typ
, Suppress
=> Access_Check
);
5084 when Attribute_Range_Length
=> Range_Length
: begin
5086 -- The only special processing required is for the case where
5087 -- Range_Length is applied to an enumeration type with holes.
5088 -- In this case we transform
5094 -- X'Pos (X'Last) - X'Pos (X'First) + 1
5096 -- So that the result reflects the proper Pos values instead
5097 -- of the underlying representations.
5099 if Is_Enumeration_Type
(Ptyp
)
5100 and then Has_Non_Standard_Rep
(Ptyp
)
5105 Make_Op_Subtract
(Loc
,
5107 Make_Attribute_Reference
(Loc
,
5108 Attribute_Name
=> Name_Pos
,
5109 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
5110 Expressions
=> New_List
(
5111 Make_Attribute_Reference
(Loc
,
5112 Attribute_Name
=> Name_Last
,
5113 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
)))),
5116 Make_Attribute_Reference
(Loc
,
5117 Attribute_Name
=> Name_Pos
,
5118 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
5119 Expressions
=> New_List
(
5120 Make_Attribute_Reference
(Loc
,
5121 Attribute_Name
=> Name_First
,
5122 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
))))),
5124 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)));
5126 Analyze_And_Resolve
(N
, Typ
);
5128 -- For all other cases, the attribute is handled by the back end, but
5129 -- we need to deal with the case of the range check on a universal
5133 Apply_Universal_Integer_Attribute_Checks
(N
);
5141 when Attribute_Read
=> Read
: declare
5142 P_Type
: constant Entity_Id
:= Entity
(Pref
);
5143 B_Type
: constant Entity_Id
:= Base_Type
(P_Type
);
5144 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
5154 -- If no underlying type, we have an error that will be diagnosed
5155 -- elsewhere, so here we just completely ignore the expansion.
5161 -- Stream operations can appear in user code even if the restriction
5162 -- No_Streams is active (for example, when instantiating a predefined
5163 -- container). In that case rewrite the attribute as a Raise to
5164 -- prevent any run-time use.
5166 if Restriction_Active
(No_Streams
) then
5168 Make_Raise_Program_Error
(Sloc
(N
),
5169 Reason
=> PE_Stream_Operation_Not_Allowed
));
5170 Set_Etype
(N
, B_Type
);
5174 -- The simple case, if there is a TSS for Read, just call it
5176 Pname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Read
);
5178 if Present
(Pname
) then
5182 -- If there is a Stream_Convert pragma, use it, we rewrite
5184 -- sourcetyp'Read (stream, Item)
5188 -- Item := sourcetyp (strmread (strmtyp'Input (Stream)));
5190 -- where strmread is the given Read function that converts an
5191 -- argument of type strmtyp to type sourcetyp or a type from which
5192 -- it is derived. The conversion to sourcetyp is required in the
5195 -- A special case arises if Item is a type conversion in which
5196 -- case, we have to expand to:
5198 -- Itemx := typex (strmread (strmtyp'Input (Stream)));
5200 -- where Itemx is the expression of the type conversion (i.e.
5201 -- the actual object), and typex is the type of Itemx.
5203 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
5205 if Present
(Prag
) then
5206 Arg2
:= Next
(First
(Pragma_Argument_Associations
(Prag
)));
5207 Rfunc
:= Entity
(Expression
(Arg2
));
5208 Lhs
:= Relocate_Node
(Next
(First
(Exprs
)));
5210 OK_Convert_To
(B_Type
,
5211 Make_Function_Call
(Loc
,
5212 Name
=> New_Occurrence_Of
(Rfunc
, Loc
),
5213 Parameter_Associations
=> New_List
(
5214 Make_Attribute_Reference
(Loc
,
5217 (Etype
(First_Formal
(Rfunc
)), Loc
),
5218 Attribute_Name
=> Name_Input
,
5219 Expressions
=> New_List
(
5220 Relocate_Node
(First
(Exprs
)))))));
5222 if Nkind
(Lhs
) = N_Type_Conversion
then
5223 Lhs
:= Expression
(Lhs
);
5224 Rhs
:= Convert_To
(Etype
(Lhs
), Rhs
);
5228 Make_Assignment_Statement
(Loc
,
5230 Expression
=> Rhs
));
5231 Set_Assignment_OK
(Lhs
);
5235 -- For elementary types, we call the I_xxx routine using the first
5236 -- parameter and then assign the result into the second parameter.
5237 -- We set Assignment_OK to deal with the conversion case.
5239 elsif Is_Elementary_Type
(U_Type
) then
5245 Lhs
:= Relocate_Node
(Next
(First
(Exprs
)));
5246 Rhs
:= Build_Elementary_Input_Call
(N
);
5248 if Nkind
(Lhs
) = N_Type_Conversion
then
5249 Lhs
:= Expression
(Lhs
);
5250 Rhs
:= Convert_To
(Etype
(Lhs
), Rhs
);
5253 Set_Assignment_OK
(Lhs
);
5256 Make_Assignment_Statement
(Loc
,
5258 Expression
=> Rhs
));
5266 elsif Is_Array_Type
(U_Type
) then
5267 Build_Array_Read_Procedure
(N
, U_Type
, Decl
, Pname
);
5268 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
5270 -- Tagged type case, use the primitive Read function. Note that
5271 -- this will dispatch in the class-wide case which is what we want
5273 elsif Is_Tagged_Type
(U_Type
) then
5274 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Read
);
5276 -- All other record type cases, including protected records. The
5277 -- latter only arise for expander generated code for handling
5278 -- shared passive partition access.
5282 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
5284 -- Ada 2005 (AI-216): Program_Error is raised when executing
5285 -- the default implementation of the Read attribute of an
5286 -- Unchecked_Union type.
5288 if Is_Unchecked_Union
(Base_Type
(U_Type
)) then
5290 Make_Raise_Program_Error
(Loc
,
5291 Reason
=> PE_Unchecked_Union_Restriction
));
5294 if Has_Discriminants
(U_Type
)
5296 (Discriminant_Default_Value
(First_Discriminant
(U_Type
)))
5298 Build_Mutable_Record_Read_Procedure
5299 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
5301 Build_Record_Read_Procedure
5302 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
5305 -- Suppress checks, uninitialized or otherwise invalid
5306 -- data does not cause constraint errors to be raised for
5307 -- a complete record read.
5309 Insert_Action
(N
, Decl
, All_Checks
);
5313 Rewrite_Stream_Proc_Call
(Pname
);
5320 -- Ref is identical to To_Address, see To_Address for processing
5326 -- Transforms 'Remainder into a call to the floating-point attribute
5327 -- function Remainder in Fat_xxx (where xxx is the root type)
5329 when Attribute_Remainder
=>
5330 Expand_Fpt_Attribute_RR
(N
);
5336 -- Transform 'Result into reference to _Result formal. At the point
5337 -- where a legal 'Result attribute is expanded, we know that we are in
5338 -- the context of a _Postcondition function with a _Result parameter.
5340 when Attribute_Result
=>
5341 Rewrite
(N
, Make_Identifier
(Loc
, Chars
=> Name_uResult
));
5342 Analyze_And_Resolve
(N
, Typ
);
5348 -- The handling of the Round attribute is quite delicate. The processing
5349 -- in Sem_Attr introduced a conversion to universal real, reflecting the
5350 -- semantics of Round, but we do not want anything to do with universal
5351 -- real at runtime, since this corresponds to using floating-point
5354 -- What we have now is that the Etype of the Round attribute correctly
5355 -- indicates the final result type. The operand of the Round is the
5356 -- conversion to universal real, described above, and the operand of
5357 -- this conversion is the actual operand of Round, which may be the
5358 -- special case of a fixed point multiplication or division (Etype =
5361 -- The exapander will expand first the operand of the conversion, then
5362 -- the conversion, and finally the round attribute itself, since we
5363 -- always work inside out. But we cannot simply process naively in this
5364 -- order. In the semantic world where universal fixed and real really
5365 -- exist and have infinite precision, there is no problem, but in the
5366 -- implementation world, where universal real is a floating-point type,
5367 -- we would get the wrong result.
5369 -- So the approach is as follows. First, when expanding a multiply or
5370 -- divide whose type is universal fixed, we do nothing at all, instead
5371 -- deferring the operation till later.
5373 -- The actual processing is done in Expand_N_Type_Conversion which
5374 -- handles the special case of Round by looking at its parent to see if
5375 -- it is a Round attribute, and if it is, handling the conversion (or
5376 -- its fixed multiply/divide child) in an appropriate manner.
5378 -- This means that by the time we get to expanding the Round attribute
5379 -- itself, the Round is nothing more than a type conversion (and will
5380 -- often be a null type conversion), so we just replace it with the
5381 -- appropriate conversion operation.
5383 when Attribute_Round
=>
5385 Convert_To
(Etype
(N
), Relocate_Node
(First
(Exprs
))));
5386 Analyze_And_Resolve
(N
);
5392 -- Transforms 'Rounding into a call to the floating-point attribute
5393 -- function Rounding in Fat_xxx (where xxx is the root type)
5394 -- Expansion is avoided for cases the back end can handle directly.
5396 when Attribute_Rounding
=>
5397 if not Is_Inline_Floating_Point_Attribute
(N
) then
5398 Expand_Fpt_Attribute_R
(N
);
5405 -- Transforms 'Scaling into a call to the floating-point attribute
5406 -- function Scaling in Fat_xxx (where xxx is the root type)
5408 when Attribute_Scaling
=>
5409 Expand_Fpt_Attribute_RI
(N
);
5411 -------------------------
5412 -- Simple_Storage_Pool --
5413 -------------------------
5415 when Attribute_Simple_Storage_Pool
=>
5417 Make_Type_Conversion
(Loc
,
5418 Subtype_Mark
=> New_Occurrence_Of
(Etype
(N
), Loc
),
5419 Expression
=> New_Occurrence_Of
(Entity
(N
), Loc
)));
5420 Analyze_And_Resolve
(N
, Typ
);
5426 when Attribute_Size |
5427 Attribute_Object_Size |
5428 Attribute_Value_Size |
5429 Attribute_VADS_Size
=> Size
:
5436 -- Processing for VADS_Size case. Note that this processing removes
5437 -- all traces of VADS_Size from the tree, and completes all required
5438 -- processing for VADS_Size by translating the attribute reference
5439 -- to an appropriate Size or Object_Size reference.
5441 if Id
= Attribute_VADS_Size
5442 or else (Use_VADS_Size
and then Id
= Attribute_Size
)
5444 -- If the size is specified, then we simply use the specified
5445 -- size. This applies to both types and objects. The size of an
5446 -- object can be specified in the following ways:
5448 -- An explicit size object is given for an object
5449 -- A component size is specified for an indexed component
5450 -- A component clause is specified for a selected component
5451 -- The object is a component of a packed composite object
5453 -- If the size is specified, then VADS_Size of an object
5455 if (Is_Entity_Name
(Pref
)
5456 and then Present
(Size_Clause
(Entity
(Pref
))))
5458 (Nkind
(Pref
) = N_Component_Clause
5459 and then (Present
(Component_Clause
5460 (Entity
(Selector_Name
(Pref
))))
5461 or else Is_Packed
(Etype
(Prefix
(Pref
)))))
5463 (Nkind
(Pref
) = N_Indexed_Component
5464 and then (Component_Size
(Etype
(Prefix
(Pref
))) /= 0
5465 or else Is_Packed
(Etype
(Prefix
(Pref
)))))
5467 Set_Attribute_Name
(N
, Name_Size
);
5469 -- Otherwise if we have an object rather than a type, then the
5470 -- VADS_Size attribute applies to the type of the object, rather
5471 -- than the object itself. This is one of the respects in which
5472 -- VADS_Size differs from Size.
5475 if (not Is_Entity_Name
(Pref
)
5476 or else not Is_Type
(Entity
(Pref
)))
5477 and then (Is_Scalar_Type
(Ptyp
) or else Is_Constrained
(Ptyp
))
5479 Rewrite
(Pref
, New_Occurrence_Of
(Ptyp
, Loc
));
5482 -- For a scalar type for which no size was explicitly given,
5483 -- VADS_Size means Object_Size. This is the other respect in
5484 -- which VADS_Size differs from Size.
5486 if Is_Scalar_Type
(Ptyp
) and then No
(Size_Clause
(Ptyp
)) then
5487 Set_Attribute_Name
(N
, Name_Object_Size
);
5489 -- In all other cases, Size and VADS_Size are the sane
5492 Set_Attribute_Name
(N
, Name_Size
);
5497 -- For class-wide types, X'Class'Size is transformed into a direct
5498 -- reference to the Size of the class type, so that the back end does
5499 -- not have to deal with the X'Class'Size reference.
5501 if Is_Entity_Name
(Pref
)
5502 and then Is_Class_Wide_Type
(Entity
(Pref
))
5504 Rewrite
(Prefix
(N
), New_Occurrence_Of
(Entity
(Pref
), Loc
));
5507 -- For X'Size applied to an object of a class-wide type, transform
5508 -- X'Size into a call to the primitive operation _Size applied to X.
5510 elsif Is_Class_Wide_Type
(Ptyp
)
5511 or else (Id
= Attribute_Size
5512 and then Is_Tagged_Type
(Ptyp
)
5513 and then Has_Unknown_Discriminants
(Ptyp
))
5515 -- No need to do anything else compiling under restriction
5516 -- No_Dispatching_Calls. During the semantic analysis we
5517 -- already notified such violation.
5519 if Restriction_Active
(No_Dispatching_Calls
) then
5524 Make_Function_Call
(Loc
,
5525 Name
=> New_Occurrence_Of
5526 (Find_Prim_Op
(Ptyp
, Name_uSize
), Loc
),
5527 Parameter_Associations
=> New_List
(Pref
));
5529 if Typ
/= Standard_Long_Long_Integer
then
5531 -- The context is a specific integer type with which the
5532 -- original attribute was compatible. The function has a
5533 -- specific type as well, so to preserve the compatibility
5534 -- we must convert explicitly.
5536 New_Node
:= Convert_To
(Typ
, New_Node
);
5539 Rewrite
(N
, New_Node
);
5540 Analyze_And_Resolve
(N
, Typ
);
5543 -- Case of known RM_Size of a type
5545 elsif (Id
= Attribute_Size
or else Id
= Attribute_Value_Size
)
5546 and then Is_Entity_Name
(Pref
)
5547 and then Is_Type
(Entity
(Pref
))
5548 and then Known_Static_RM_Size
(Entity
(Pref
))
5550 Siz
:= RM_Size
(Entity
(Pref
));
5552 -- Case of known Esize of a type
5554 elsif Id
= Attribute_Object_Size
5555 and then Is_Entity_Name
(Pref
)
5556 and then Is_Type
(Entity
(Pref
))
5557 and then Known_Static_Esize
(Entity
(Pref
))
5559 Siz
:= Esize
(Entity
(Pref
));
5561 -- Case of known size of object
5563 elsif Id
= Attribute_Size
5564 and then Is_Entity_Name
(Pref
)
5565 and then Is_Object
(Entity
(Pref
))
5566 and then Known_Esize
(Entity
(Pref
))
5567 and then Known_Static_Esize
(Entity
(Pref
))
5569 Siz
:= Esize
(Entity
(Pref
));
5571 -- For an array component, we can do Size in the front end
5572 -- if the component_size of the array is set.
5574 elsif Nkind
(Pref
) = N_Indexed_Component
then
5575 Siz
:= Component_Size
(Etype
(Prefix
(Pref
)));
5577 -- For a record component, we can do Size in the front end if there
5578 -- is a component clause, or if the record is packed and the
5579 -- component's size is known at compile time.
5581 elsif Nkind
(Pref
) = N_Selected_Component
then
5583 Rec
: constant Entity_Id
:= Etype
(Prefix
(Pref
));
5584 Comp
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
5587 if Present
(Component_Clause
(Comp
)) then
5588 Siz
:= Esize
(Comp
);
5590 elsif Is_Packed
(Rec
) then
5591 Siz
:= RM_Size
(Ptyp
);
5594 Apply_Universal_Integer_Attribute_Checks
(N
);
5599 -- All other cases are handled by the back end
5602 Apply_Universal_Integer_Attribute_Checks
(N
);
5604 -- If Size is applied to a formal parameter that is of a packed
5605 -- array subtype, then apply Size to the actual subtype.
5607 if Is_Entity_Name
(Pref
)
5608 and then Is_Formal
(Entity
(Pref
))
5609 and then Is_Array_Type
(Ptyp
)
5610 and then Is_Packed
(Ptyp
)
5613 Make_Attribute_Reference
(Loc
,
5615 New_Occurrence_Of
(Get_Actual_Subtype
(Pref
), Loc
),
5616 Attribute_Name
=> Name_Size
));
5617 Analyze_And_Resolve
(N
, Typ
);
5620 -- If Size applies to a dereference of an access to unconstrained
5621 -- packed array, the back end needs to see its unconstrained
5622 -- nominal type, but also a hint to the actual constrained type.
5624 if Nkind
(Pref
) = N_Explicit_Dereference
5625 and then Is_Array_Type
(Ptyp
)
5626 and then not Is_Constrained
(Ptyp
)
5627 and then Is_Packed
(Ptyp
)
5629 Set_Actual_Designated_Subtype
(Pref
,
5630 Get_Actual_Subtype
(Pref
));
5636 -- Common processing for record and array component case
5638 if Siz
/= No_Uint
and then Siz
/= 0 then
5640 CS
: constant Boolean := Comes_From_Source
(N
);
5643 Rewrite
(N
, Make_Integer_Literal
(Loc
, Siz
));
5645 -- This integer literal is not a static expression. We do not
5646 -- call Analyze_And_Resolve here, because this would activate
5647 -- the circuit for deciding that a static value was out of
5648 -- range, and we don't want that.
5650 -- So just manually set the type, mark the expression as non-
5651 -- static, and then ensure that the result is checked properly
5652 -- if the attribute comes from source (if it was internally
5653 -- generated, we never need a constraint check).
5656 Set_Is_Static_Expression
(N
, False);
5659 Apply_Constraint_Check
(N
, Typ
);
5669 when Attribute_Storage_Pool
=>
5671 Make_Type_Conversion
(Loc
,
5672 Subtype_Mark
=> New_Occurrence_Of
(Etype
(N
), Loc
),
5673 Expression
=> New_Occurrence_Of
(Entity
(N
), Loc
)));
5674 Analyze_And_Resolve
(N
, Typ
);
5680 when Attribute_Storage_Size
=> Storage_Size
: declare
5681 Alloc_Op
: Entity_Id
:= Empty
;
5685 -- Access type case, always go to the root type
5687 -- The case of access types results in a value of zero for the case
5688 -- where no storage size attribute clause has been given. If a
5689 -- storage size has been given, then the attribute is converted
5690 -- to a reference to the variable used to hold this value.
5692 if Is_Access_Type
(Ptyp
) then
5693 if Present
(Storage_Size_Variable
(Root_Type
(Ptyp
))) then
5695 Make_Attribute_Reference
(Loc
,
5696 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
5697 Attribute_Name
=> Name_Max
,
5698 Expressions
=> New_List
(
5699 Make_Integer_Literal
(Loc
, 0),
5702 (Storage_Size_Variable
(Root_Type
(Ptyp
)), Loc
)))));
5704 elsif Present
(Associated_Storage_Pool
(Root_Type
(Ptyp
))) then
5706 -- If the access type is associated with a simple storage pool
5707 -- object, then attempt to locate the optional Storage_Size
5708 -- function of the simple storage pool type. If not found,
5709 -- then the result will default to zero.
5711 if Present
(Get_Rep_Pragma
(Root_Type
(Ptyp
),
5712 Name_Simple_Storage_Pool_Type
))
5715 Pool_Type
: constant Entity_Id
:=
5716 Base_Type
(Etype
(Entity
(N
)));
5719 Alloc_Op
:= Get_Name_Entity_Id
(Name_Storage_Size
);
5720 while Present
(Alloc_Op
) loop
5721 if Scope
(Alloc_Op
) = Scope
(Pool_Type
)
5722 and then Present
(First_Formal
(Alloc_Op
))
5723 and then Etype
(First_Formal
(Alloc_Op
)) = Pool_Type
5728 Alloc_Op
:= Homonym
(Alloc_Op
);
5732 -- In the normal Storage_Pool case, retrieve the primitive
5733 -- function associated with the pool type.
5738 (Etype
(Associated_Storage_Pool
(Root_Type
(Ptyp
))),
5739 Attribute_Name
(N
));
5742 -- If Storage_Size wasn't found (can only occur in the simple
5743 -- storage pool case), then simply use zero for the result.
5745 if not Present
(Alloc_Op
) then
5746 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
5748 -- Otherwise, rewrite the allocator as a call to pool type's
5749 -- Storage_Size function.
5754 Make_Function_Call
(Loc
,
5756 New_Occurrence_Of
(Alloc_Op
, Loc
),
5758 Parameter_Associations
=> New_List
(
5760 (Associated_Storage_Pool
5761 (Root_Type
(Ptyp
)), Loc
)))));
5765 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
5768 Analyze_And_Resolve
(N
, Typ
);
5770 -- For tasks, we retrieve the size directly from the TCB. The
5771 -- size may depend on a discriminant of the type, and therefore
5772 -- can be a per-object expression, so type-level information is
5773 -- not sufficient in general. There are four cases to consider:
5775 -- a) If the attribute appears within a task body, the designated
5776 -- TCB is obtained by a call to Self.
5778 -- b) If the prefix of the attribute is the name of a task object,
5779 -- the designated TCB is the one stored in the corresponding record.
5781 -- c) If the prefix is a task type, the size is obtained from the
5782 -- size variable created for each task type
5784 -- d) If no storage_size was specified for the type , there is no
5785 -- size variable, and the value is a system-specific default.
5788 if In_Open_Scopes
(Ptyp
) then
5790 -- Storage_Size (Self)
5794 Make_Function_Call
(Loc
,
5796 New_Occurrence_Of
(RTE
(RE_Storage_Size
), Loc
),
5797 Parameter_Associations
=>
5799 Make_Function_Call
(Loc
,
5801 New_Occurrence_Of
(RTE
(RE_Self
), Loc
))))));
5803 elsif not Is_Entity_Name
(Pref
)
5804 or else not Is_Type
(Entity
(Pref
))
5806 -- Storage_Size (Rec (Obj).Size)
5810 Make_Function_Call
(Loc
,
5812 New_Occurrence_Of
(RTE
(RE_Storage_Size
), Loc
),
5813 Parameter_Associations
=>
5815 Make_Selected_Component
(Loc
,
5817 Unchecked_Convert_To
(
5818 Corresponding_Record_Type
(Ptyp
),
5819 New_Copy_Tree
(Pref
)),
5821 Make_Identifier
(Loc
, Name_uTask_Id
))))));
5823 elsif Present
(Storage_Size_Variable
(Ptyp
)) then
5825 -- Static storage size pragma given for type: retrieve value
5826 -- from its allocated storage variable.
5830 Make_Function_Call
(Loc
,
5831 Name
=> New_Occurrence_Of
(
5832 RTE
(RE_Adjust_Storage_Size
), Loc
),
5833 Parameter_Associations
=>
5836 Storage_Size_Variable
(Ptyp
), Loc
)))));
5838 -- Get system default
5842 Make_Function_Call
(Loc
,
5845 RTE
(RE_Default_Stack_Size
), Loc
))));
5848 Analyze_And_Resolve
(N
, Typ
);
5856 when Attribute_Stream_Size
=>
5858 Make_Integer_Literal
(Loc
, Intval
=> Get_Stream_Size
(Ptyp
)));
5859 Analyze_And_Resolve
(N
, Typ
);
5865 -- 1. Deal with enumeration types with holes.
5866 -- 2. For floating-point, generate call to attribute function.
5867 -- 3. For other cases, deal with constraint checking.
5869 when Attribute_Succ
=> Succ
: declare
5870 Etyp
: constant Entity_Id
:= Base_Type
(Ptyp
);
5874 -- For enumeration types with non-standard representations, we
5875 -- expand typ'Succ (x) into
5877 -- Pos_To_Rep (Rep_To_Pos (x) + 1)
5879 -- If the representation is contiguous, we compute instead
5880 -- Lit1 + Rep_to_Pos (x+1), to catch invalid representations.
5882 if Is_Enumeration_Type
(Ptyp
)
5883 and then Present
(Enum_Pos_To_Rep
(Etyp
))
5885 if Has_Contiguous_Rep
(Etyp
) then
5887 Unchecked_Convert_To
(Ptyp
,
5890 Make_Integer_Literal
(Loc
,
5891 Enumeration_Rep
(First_Literal
(Ptyp
))),
5893 Make_Function_Call
(Loc
,
5896 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
5898 Parameter_Associations
=>
5900 Unchecked_Convert_To
(Ptyp
,
5903 Unchecked_Convert_To
(Standard_Integer
,
5904 Relocate_Node
(First
(Exprs
))),
5906 Make_Integer_Literal
(Loc
, 1))),
5907 Rep_To_Pos_Flag
(Ptyp
, Loc
))))));
5909 -- Add Boolean parameter True, to request program errror if
5910 -- we have a bad representation on our hands. Add False if
5911 -- checks are suppressed.
5913 Append_To
(Exprs
, Rep_To_Pos_Flag
(Ptyp
, Loc
));
5915 Make_Indexed_Component
(Loc
,
5918 (Enum_Pos_To_Rep
(Etyp
), Loc
),
5919 Expressions
=> New_List
(
5922 Make_Function_Call
(Loc
,
5925 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
5926 Parameter_Associations
=> Exprs
),
5927 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)))));
5930 Analyze_And_Resolve
(N
, Typ
);
5932 -- For floating-point, we transform 'Succ into a call to the Succ
5933 -- floating-point attribute function in Fat_xxx (xxx is root type)
5935 elsif Is_Floating_Point_Type
(Ptyp
) then
5936 Expand_Fpt_Attribute_R
(N
);
5937 Analyze_And_Resolve
(N
, Typ
);
5939 -- For modular types, nothing to do (no overflow, since wraps)
5941 elsif Is_Modular_Integer_Type
(Ptyp
) then
5944 -- For other types, if argument is marked as needing a range check or
5945 -- overflow checking is enabled, we must generate a check.
5947 elsif not Overflow_Checks_Suppressed
(Ptyp
)
5948 or else Do_Range_Check
(First
(Exprs
))
5950 Set_Do_Range_Check
(First
(Exprs
), False);
5951 Expand_Pred_Succ_Attribute
(N
);
5959 -- Transforms X'Tag into a direct reference to the tag of X
5961 when Attribute_Tag
=> Tag
: declare
5963 Prefix_Is_Type
: Boolean;
5966 if Is_Entity_Name
(Pref
) and then Is_Type
(Entity
(Pref
)) then
5967 Ttyp
:= Entity
(Pref
);
5968 Prefix_Is_Type
:= True;
5971 Prefix_Is_Type
:= False;
5974 if Is_Class_Wide_Type
(Ttyp
) then
5975 Ttyp
:= Root_Type
(Ttyp
);
5978 Ttyp
:= Underlying_Type
(Ttyp
);
5980 -- Ada 2005: The type may be a synchronized tagged type, in which
5981 -- case the tag information is stored in the corresponding record.
5983 if Is_Concurrent_Type
(Ttyp
) then
5984 Ttyp
:= Corresponding_Record_Type
(Ttyp
);
5987 if Prefix_Is_Type
then
5989 -- For VMs we leave the type attribute unexpanded because
5990 -- there's not a dispatching table to reference.
5992 if Tagged_Type_Expansion
then
5994 Unchecked_Convert_To
(RTE
(RE_Tag
),
5996 (Node
(First_Elmt
(Access_Disp_Table
(Ttyp
))), Loc
)));
5997 Analyze_And_Resolve
(N
, RTE
(RE_Tag
));
6000 -- Ada 2005 (AI-251): The use of 'Tag in the sources always
6001 -- references the primary tag of the actual object. If 'Tag is
6002 -- applied to class-wide interface objects we generate code that
6003 -- displaces "this" to reference the base of the object.
6005 elsif Comes_From_Source
(N
)
6006 and then Is_Class_Wide_Type
(Etype
(Prefix
(N
)))
6007 and then Is_Interface
(Etype
(Prefix
(N
)))
6010 -- (To_Tag_Ptr (Prefix'Address)).all
6012 -- Note that Prefix'Address is recursively expanded into a call
6013 -- to Base_Address (Obj.Tag)
6015 -- Not needed for VM targets, since all handled by the VM
6017 if Tagged_Type_Expansion
then
6019 Make_Explicit_Dereference
(Loc
,
6020 Unchecked_Convert_To
(RTE
(RE_Tag_Ptr
),
6021 Make_Attribute_Reference
(Loc
,
6022 Prefix
=> Relocate_Node
(Pref
),
6023 Attribute_Name
=> Name_Address
))));
6024 Analyze_And_Resolve
(N
, RTE
(RE_Tag
));
6029 Make_Selected_Component
(Loc
,
6030 Prefix
=> Relocate_Node
(Pref
),
6032 New_Occurrence_Of
(First_Tag_Component
(Ttyp
), Loc
)));
6033 Analyze_And_Resolve
(N
, RTE
(RE_Tag
));
6041 -- Transforms 'Terminated attribute into a call to Terminated function
6043 when Attribute_Terminated
=> Terminated
:
6045 -- The prefix of Terminated is of a task interface class-wide type.
6047 -- terminated (Task_Id (Pref._disp_get_task_id));
6049 if Ada_Version
>= Ada_2005
6050 and then Ekind
(Ptyp
) = E_Class_Wide_Type
6051 and then Is_Interface
(Ptyp
)
6052 and then Is_Task_Interface
(Ptyp
)
6055 Make_Function_Call
(Loc
,
6057 New_Occurrence_Of
(RTE
(RE_Terminated
), Loc
),
6058 Parameter_Associations
=> New_List
(
6059 Make_Unchecked_Type_Conversion
(Loc
,
6061 New_Occurrence_Of
(RTE
(RO_ST_Task_Id
), Loc
),
6063 Make_Selected_Component
(Loc
,
6065 New_Copy_Tree
(Pref
),
6067 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
))))));
6069 elsif Restricted_Profile
then
6071 Build_Call_With_Task
(Pref
, RTE
(RE_Restricted_Terminated
)));
6075 Build_Call_With_Task
(Pref
, RTE
(RE_Terminated
)));
6078 Analyze_And_Resolve
(N
, Standard_Boolean
);
6085 -- Transforms System'To_Address (X) and System.Address'Ref (X) into
6086 -- unchecked conversion from (integral) type of X to type address.
6088 when Attribute_To_Address | Attribute_Ref
=>
6090 Unchecked_Convert_To
(RTE
(RE_Address
),
6091 Relocate_Node
(First
(Exprs
))));
6092 Analyze_And_Resolve
(N
, RTE
(RE_Address
));
6098 when Attribute_To_Any
=> To_Any
: declare
6099 P_Type
: constant Entity_Id
:= Etype
(Pref
);
6100 Decls
: constant List_Id
:= New_List
;
6106 Relocate_Node
(First
(Exprs
))), Decls
));
6107 Insert_Actions
(N
, Decls
);
6108 Analyze_And_Resolve
(N
, RTE
(RE_Any
));
6115 -- Transforms 'Truncation into a call to the floating-point attribute
6116 -- function Truncation in Fat_xxx (where xxx is the root type).
6117 -- Expansion is avoided for cases the back end can handle directly.
6119 when Attribute_Truncation
=>
6120 if not Is_Inline_Floating_Point_Attribute
(N
) then
6121 Expand_Fpt_Attribute_R
(N
);
6128 when Attribute_TypeCode
=> TypeCode
: declare
6129 P_Type
: constant Entity_Id
:= Etype
(Pref
);
6130 Decls
: constant List_Id
:= New_List
;
6132 Rewrite
(N
, Build_TypeCode_Call
(Loc
, P_Type
, Decls
));
6133 Insert_Actions
(N
, Decls
);
6134 Analyze_And_Resolve
(N
, RTE
(RE_TypeCode
));
6137 -----------------------
6138 -- Unbiased_Rounding --
6139 -----------------------
6141 -- Transforms 'Unbiased_Rounding into a call to the floating-point
6142 -- attribute function Unbiased_Rounding in Fat_xxx (where xxx is the
6143 -- root type). Expansion is avoided for cases the back end can handle
6146 when Attribute_Unbiased_Rounding
=>
6147 if not Is_Inline_Floating_Point_Attribute
(N
) then
6148 Expand_Fpt_Attribute_R
(N
);
6155 when Attribute_UET_Address
=> UET_Address
: declare
6156 Ent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
6160 Make_Object_Declaration
(Loc
,
6161 Defining_Identifier
=> Ent
,
6162 Aliased_Present
=> True,
6163 Object_Definition
=>
6164 New_Occurrence_Of
(RTE
(RE_Address
), Loc
)));
6166 -- Construct name __gnat_xxx__SDP, where xxx is the unit name
6167 -- in normal external form.
6169 Get_External_Unit_Name_String
(Get_Unit_Name
(Pref
));
6170 Name_Buffer
(1 + 7 .. Name_Len
+ 7) := Name_Buffer
(1 .. Name_Len
);
6171 Name_Len
:= Name_Len
+ 7;
6172 Name_Buffer
(1 .. 7) := "__gnat_";
6173 Name_Buffer
(Name_Len
+ 1 .. Name_Len
+ 5) := "__SDP";
6174 Name_Len
:= Name_Len
+ 5;
6176 Set_Is_Imported
(Ent
);
6177 Set_Interface_Name
(Ent
,
6178 Make_String_Literal
(Loc
,
6179 Strval
=> String_From_Name_Buffer
));
6181 -- Set entity as internal to ensure proper Sprint output of its
6182 -- implicit importation.
6184 Set_Is_Internal
(Ent
);
6187 Make_Attribute_Reference
(Loc
,
6188 Prefix
=> New_Occurrence_Of
(Ent
, Loc
),
6189 Attribute_Name
=> Name_Address
));
6191 Analyze_And_Resolve
(N
, Typ
);
6198 when Attribute_Update
=>
6199 Expand_Update_Attribute
(N
);
6205 -- The processing for VADS_Size is shared with Size
6211 -- For enumeration types with a standard representation, and for all
6212 -- other types, Val is handled by the back end. For enumeration types
6213 -- with a non-standard representation we use the _Pos_To_Rep array that
6214 -- was created when the type was frozen.
6216 when Attribute_Val
=> Val
: declare
6217 Etyp
: constant Entity_Id
:= Base_Type
(Entity
(Pref
));
6220 if Is_Enumeration_Type
(Etyp
)
6221 and then Present
(Enum_Pos_To_Rep
(Etyp
))
6223 if Has_Contiguous_Rep
(Etyp
) then
6225 Rep_Node
: constant Node_Id
:=
6226 Unchecked_Convert_To
(Etyp
,
6229 Make_Integer_Literal
(Loc
,
6230 Enumeration_Rep
(First_Literal
(Etyp
))),
6232 (Convert_To
(Standard_Integer
,
6233 Relocate_Node
(First
(Exprs
))))));
6237 Unchecked_Convert_To
(Etyp
,
6240 Make_Integer_Literal
(Loc
,
6241 Enumeration_Rep
(First_Literal
(Etyp
))),
6243 Make_Function_Call
(Loc
,
6246 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
6247 Parameter_Associations
=> New_List
(
6249 Rep_To_Pos_Flag
(Etyp
, Loc
))))));
6254 Make_Indexed_Component
(Loc
,
6255 Prefix
=> New_Occurrence_Of
(Enum_Pos_To_Rep
(Etyp
), Loc
),
6256 Expressions
=> New_List
(
6257 Convert_To
(Standard_Integer
,
6258 Relocate_Node
(First
(Exprs
))))));
6261 Analyze_And_Resolve
(N
, Typ
);
6263 -- If the argument is marked as requiring a range check then generate
6266 elsif Do_Range_Check
(First
(Exprs
)) then
6267 Generate_Range_Check
(First
(Exprs
), Etyp
, CE_Range_Check_Failed
);
6275 -- The code for valid is dependent on the particular types involved.
6276 -- See separate sections below for the generated code in each case.
6278 when Attribute_Valid
=> Valid
: declare
6279 Btyp
: Entity_Id
:= Base_Type
(Ptyp
);
6282 Save_Validity_Checks_On
: constant Boolean := Validity_Checks_On
;
6283 -- Save the validity checking mode. We always turn off validity
6284 -- checking during process of 'Valid since this is one place
6285 -- where we do not want the implicit validity checks to intefere
6286 -- with the explicit validity check that the programmer is doing.
6288 function Make_Range_Test
return Node_Id
;
6289 -- Build the code for a range test of the form
6290 -- Btyp!(Pref) in Btyp!(Ptyp'First) .. Btyp!(Ptyp'Last)
6292 ---------------------
6293 -- Make_Range_Test --
6294 ---------------------
6296 function Make_Range_Test
return Node_Id
is
6297 Temp
: constant Node_Id
:= Duplicate_Subexpr
(Pref
);
6300 -- The value whose validity is being checked has been captured in
6301 -- an object declaration. We certainly don't want this object to
6302 -- appear valid because the declaration initializes it.
6304 if Is_Entity_Name
(Temp
) then
6305 Set_Is_Known_Valid
(Entity
(Temp
), False);
6311 Unchecked_Convert_To
(Btyp
, Temp
),
6315 Unchecked_Convert_To
(Btyp
,
6316 Make_Attribute_Reference
(Loc
,
6317 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
6318 Attribute_Name
=> Name_First
)),
6320 Unchecked_Convert_To
(Btyp
,
6321 Make_Attribute_Reference
(Loc
,
6322 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
6323 Attribute_Name
=> Name_Last
))));
6324 end Make_Range_Test
;
6326 -- Start of processing for Attribute_Valid
6329 -- Do not expand sourced code 'Valid reference in CodePeer mode,
6330 -- will be handled by the back-end directly.
6332 if CodePeer_Mode
and then Comes_From_Source
(N
) then
6336 -- Turn off validity checks. We do not want any implicit validity
6337 -- checks to intefere with the explicit check from the attribute
6339 Validity_Checks_On
:= False;
6341 -- Retrieve the base type. Handle the case where the base type is a
6342 -- private enumeration type.
6344 if Is_Private_Type
(Btyp
) and then Present
(Full_View
(Btyp
)) then
6345 Btyp
:= Full_View
(Btyp
);
6348 -- Floating-point case. This case is handled by the Valid attribute
6349 -- code in the floating-point attribute run-time library.
6351 if Is_Floating_Point_Type
(Ptyp
) then
6352 Float_Valid
: declare
6356 function Get_Fat_Entity
(Nam
: Name_Id
) return Entity_Id
;
6357 -- Return entity for Pkg.Nam
6359 --------------------
6360 -- Get_Fat_Entity --
6361 --------------------
6363 function Get_Fat_Entity
(Nam
: Name_Id
) return Entity_Id
is
6364 Exp_Name
: constant Node_Id
:=
6365 Make_Selected_Component
(Loc
,
6366 Prefix
=> New_Occurrence_Of
(RTE
(Pkg
), Loc
),
6367 Selector_Name
=> Make_Identifier
(Loc
, Nam
));
6369 Find_Selected_Component
(Exp_Name
);
6370 return Entity
(Exp_Name
);
6373 -- Start of processing for Float_Valid
6376 case Float_Rep
(Btyp
) is
6378 -- The AAMP back end handles Valid for floating-point types
6381 Analyze_And_Resolve
(Pref
, Ptyp
);
6382 Set_Etype
(N
, Standard_Boolean
);
6386 Find_Fat_Info
(Ptyp
, Ftp
, Pkg
);
6388 -- If the prefix is a reverse SSO component, or is
6389 -- possibly unaligned, first create a temporary copy
6390 -- that is in native SSO, and properly aligned. Make it
6391 -- Volatile to prevent folding in the back-end. Note
6392 -- that we use an intermediate constrained string type
6393 -- to initialize the temporary, as the value at hand
6394 -- might be invalid, and in that case it cannot be copied
6395 -- using a floating point register.
6397 if In_Reverse_Storage_Order_Object
(Pref
)
6399 Is_Possibly_Unaligned_Object
(Pref
)
6402 Temp
: constant Entity_Id
:=
6403 Make_Temporary
(Loc
, 'F');
6405 Fat_S
: constant Entity_Id
:=
6406 Get_Fat_Entity
(Name_S
);
6407 -- Constrained string subtype of appropriate size
6409 Fat_P
: constant Entity_Id
:=
6410 Get_Fat_Entity
(Name_P
);
6413 Decl
: constant Node_Id
:=
6414 Make_Object_Declaration
(Loc
,
6415 Defining_Identifier
=> Temp
,
6416 Aliased_Present
=> True,
6417 Object_Definition
=>
6418 New_Occurrence_Of
(Ptyp
, Loc
));
6421 Set_Aspect_Specifications
(Decl
, New_List
(
6422 Make_Aspect_Specification
(Loc
,
6424 Make_Identifier
(Loc
, Name_Volatile
))));
6430 Make_Assignment_Statement
(Loc
,
6432 Make_Explicit_Dereference
(Loc
,
6434 Unchecked_Convert_To
(Fat_P
,
6435 Make_Attribute_Reference
(Loc
,
6437 New_Occurrence_Of
(Temp
, Loc
),
6439 Name_Unrestricted_Access
))),
6441 Unchecked_Convert_To
(Fat_S
,
6442 Relocate_Node
(Pref
)))),
6444 Suppress
=> All_Checks
);
6446 Rewrite
(Pref
, New_Occurrence_Of
(Temp
, Loc
));
6450 -- We now have an object of the proper endianness and
6451 -- alignment, and can construct a Valid attribute.
6453 -- We make sure the prefix of this valid attribute is
6454 -- marked as not coming from source, to avoid losing
6455 -- warnings from 'Valid looking like a possible update.
6457 Set_Comes_From_Source
(Pref
, False);
6459 Expand_Fpt_Attribute
6460 (N
, Pkg
, Name_Valid
,
6462 Make_Attribute_Reference
(Loc
,
6463 Prefix
=> Unchecked_Convert_To
(Ftp
, Pref
),
6464 Attribute_Name
=> Name_Unrestricted_Access
)));
6467 -- One more task, we still need a range check. Required
6468 -- only if we have a constraint, since the Valid routine
6469 -- catches infinities properly (infinities are never valid).
6471 -- The way we do the range check is simply to create the
6472 -- expression: Valid (N) and then Base_Type(Pref) in Typ.
6474 if not Subtypes_Statically_Match
(Ptyp
, Btyp
) then
6477 Left_Opnd
=> Relocate_Node
(N
),
6480 Left_Opnd
=> Convert_To
(Btyp
, Pref
),
6481 Right_Opnd
=> New_Occurrence_Of
(Ptyp
, Loc
))));
6485 -- Enumeration type with holes
6487 -- For enumeration types with holes, the Pos value constructed by
6488 -- the Enum_Rep_To_Pos function built in Exp_Ch3 called with a
6489 -- second argument of False returns minus one for an invalid value,
6490 -- and the non-negative pos value for a valid value, so the
6491 -- expansion of X'Valid is simply:
6493 -- type(X)'Pos (X) >= 0
6495 -- We can't quite generate it that way because of the requirement
6496 -- for the non-standard second argument of False in the resulting
6497 -- rep_to_pos call, so we have to explicitly create:
6499 -- _rep_to_pos (X, False) >= 0
6501 -- If we have an enumeration subtype, we also check that the
6502 -- value is in range:
6504 -- _rep_to_pos (X, False) >= 0
6506 -- (X >= type(X)'First and then type(X)'Last <= X)
6508 elsif Is_Enumeration_Type
(Ptyp
)
6509 and then Present
(Enum_Pos_To_Rep
(Btyp
))
6514 Make_Function_Call
(Loc
,
6516 New_Occurrence_Of
(TSS
(Btyp
, TSS_Rep_To_Pos
), Loc
),
6517 Parameter_Associations
=> New_List
(
6519 New_Occurrence_Of
(Standard_False
, Loc
))),
6520 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0));
6524 (Type_Low_Bound
(Ptyp
) /= Type_Low_Bound
(Btyp
)
6526 Type_High_Bound
(Ptyp
) /= Type_High_Bound
(Btyp
))
6528 -- The call to Make_Range_Test will create declarations
6529 -- that need a proper insertion point, but Pref is now
6530 -- attached to a node with no ancestor. Attach to tree
6531 -- even if it is to be rewritten below.
6533 Set_Parent
(Tst
, Parent
(N
));
6537 Left_Opnd
=> Make_Range_Test
,
6543 -- Fortran convention booleans
6545 -- For the very special case of Fortran convention booleans, the
6546 -- value is always valid, since it is an integer with the semantics
6547 -- that non-zero is true, and any value is permissible.
6549 elsif Is_Boolean_Type
(Ptyp
)
6550 and then Convention
(Ptyp
) = Convention_Fortran
6552 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
6554 -- For biased representations, we will be doing an unchecked
6555 -- conversion without unbiasing the result. That means that the range
6556 -- test has to take this into account, and the proper form of the
6559 -- Btyp!(Pref) < Btyp!(Ptyp'Range_Length)
6561 elsif Has_Biased_Representation
(Ptyp
) then
6562 Btyp
:= RTE
(RE_Unsigned_32
);
6566 Unchecked_Convert_To
(Btyp
, Duplicate_Subexpr
(Pref
)),
6568 Unchecked_Convert_To
(Btyp
,
6569 Make_Attribute_Reference
(Loc
,
6570 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
6571 Attribute_Name
=> Name_Range_Length
))));
6573 -- For all other scalar types, what we want logically is a
6576 -- X in type(X)'First .. type(X)'Last
6578 -- But that's precisely what won't work because of possible
6579 -- unwanted optimization (and indeed the basic motivation for
6580 -- the Valid attribute is exactly that this test does not work).
6581 -- What will work is:
6583 -- Btyp!(X) >= Btyp!(type(X)'First)
6585 -- Btyp!(X) <= Btyp!(type(X)'Last)
6587 -- where Btyp is an integer type large enough to cover the full
6588 -- range of possible stored values (i.e. it is chosen on the basis
6589 -- of the size of the type, not the range of the values). We write
6590 -- this as two tests, rather than a range check, so that static
6591 -- evaluation will easily remove either or both of the checks if
6592 -- they can be -statically determined to be true (this happens
6593 -- when the type of X is static and the range extends to the full
6594 -- range of stored values).
6596 -- Unsigned types. Note: it is safe to consider only whether the
6597 -- subtype is unsigned, since we will in that case be doing all
6598 -- unsigned comparisons based on the subtype range. Since we use the
6599 -- actual subtype object size, this is appropriate.
6601 -- For example, if we have
6603 -- subtype x is integer range 1 .. 200;
6604 -- for x'Object_Size use 8;
6606 -- Now the base type is signed, but objects of this type are bits
6607 -- unsigned, and doing an unsigned test of the range 1 to 200 is
6608 -- correct, even though a value greater than 127 looks signed to a
6609 -- signed comparison.
6611 elsif Is_Unsigned_Type
(Ptyp
) then
6612 if Esize
(Ptyp
) <= 32 then
6613 Btyp
:= RTE
(RE_Unsigned_32
);
6615 Btyp
:= RTE
(RE_Unsigned_64
);
6618 Rewrite
(N
, Make_Range_Test
);
6623 if Esize
(Ptyp
) <= Esize
(Standard_Integer
) then
6624 Btyp
:= Standard_Integer
;
6626 Btyp
:= Universal_Integer
;
6629 Rewrite
(N
, Make_Range_Test
);
6632 -- If a predicate is present, then we do the predicate test, even if
6633 -- within the predicate function (infinite recursion is warned about
6634 -- in Sem_Attr in that case).
6637 Pred_Func
: constant Entity_Id
:= Predicate_Function
(Ptyp
);
6640 if Present
(Pred_Func
) then
6643 Left_Opnd
=> Relocate_Node
(N
),
6644 Right_Opnd
=> Make_Predicate_Call
(Ptyp
, Pref
)));
6648 Analyze_And_Resolve
(N
, Standard_Boolean
);
6649 Validity_Checks_On
:= Save_Validity_Checks_On
;
6656 when Attribute_Valid_Scalars
=> Valid_Scalars
: declare
6660 if Present
(Underlying_Type
(Ptyp
)) then
6661 Ftyp
:= Underlying_Type
(Ptyp
);
6666 -- Replace by True if no scalar parts
6668 if not Scalar_Part_Present
(Ftyp
) then
6669 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
6671 -- For scalar types, Valid_Scalars is the same as Valid
6673 elsif Is_Scalar_Type
(Ftyp
) then
6675 Make_Attribute_Reference
(Loc
,
6676 Attribute_Name
=> Name_Valid
,
6679 -- For array types, we construct a function that determines if there
6680 -- are any non-valid scalar subcomponents, and call the function.
6681 -- We only do this for arrays whose component type needs checking
6683 elsif Is_Array_Type
(Ftyp
)
6684 and then Scalar_Part_Present
(Component_Type
(Ftyp
))
6687 Make_Function_Call
(Loc
,
6689 New_Occurrence_Of
(Build_Array_VS_Func
(Ftyp
, N
), Loc
),
6690 Parameter_Associations
=> New_List
(Pref
)));
6692 -- For record types, we construct a function that determines if there
6693 -- are any non-valid scalar subcomponents, and call the function.
6695 elsif Is_Record_Type
(Ftyp
)
6696 and then Nkind
(Type_Definition
(Declaration_Node
(Ftyp
))) =
6700 Make_Function_Call
(Loc
,
6702 New_Occurrence_Of
(Build_Record_VS_Func
(Ftyp
, N
), Loc
),
6703 Parameter_Associations
=> New_List
(Pref
)));
6705 -- Other record types or types with discriminants
6707 elsif Is_Record_Type
(Ftyp
) or else Has_Discriminants
(Ptyp
) then
6709 -- Build expression with list of equality tests
6717 X
:= New_Occurrence_Of
(Standard_True
, Loc
);
6718 C
:= First_Component_Or_Discriminant
(Ptyp
);
6719 while Present
(C
) loop
6720 if not Scalar_Part_Present
(Etype
(C
)) then
6722 elsif Is_Scalar_Type
(Etype
(C
)) then
6725 A
:= Name_Valid_Scalars
;
6732 Make_Attribute_Reference
(Loc
,
6733 Attribute_Name
=> A
,
6735 Make_Selected_Component
(Loc
,
6737 Duplicate_Subexpr
(Pref
, Name_Req
=> True),
6739 New_Occurrence_Of
(C
, Loc
))));
6741 Next_Component_Or_Discriminant
(C
);
6747 -- For all other types, result is True
6750 Rewrite
(N
, New_Occurrence_Of
(Standard_Boolean
, Loc
));
6753 -- Result is always boolean, but never static
6755 Analyze_And_Resolve
(N
, Standard_Boolean
);
6756 Set_Is_Static_Expression
(N
, False);
6763 -- Value attribute is handled in separate unit Exp_Imgv
6765 when Attribute_Value
=>
6766 Exp_Imgv
.Expand_Value_Attribute
(N
);
6772 -- The processing for Value_Size shares the processing for Size
6778 -- The processing for Version shares the processing for Body_Version
6784 -- Wide_Image attribute is handled in separate unit Exp_Imgv
6786 when Attribute_Wide_Image
=>
6787 Exp_Imgv
.Expand_Wide_Image_Attribute
(N
);
6789 ---------------------
6790 -- Wide_Wide_Image --
6791 ---------------------
6793 -- Wide_Wide_Image attribute is handled in separate unit Exp_Imgv
6795 when Attribute_Wide_Wide_Image
=>
6796 Exp_Imgv
.Expand_Wide_Wide_Image_Attribute
(N
);
6802 -- We expand typ'Wide_Value (X) into
6805 -- (Wide_String_To_String (X, Wide_Character_Encoding_Method))
6807 -- Wide_String_To_String is a runtime function that converts its wide
6808 -- string argument to String, converting any non-translatable characters
6809 -- into appropriate escape sequences. This preserves the required
6810 -- semantics of Wide_Value in all cases, and results in a very simple
6811 -- implementation approach.
6813 -- Note: for this approach to be fully standard compliant for the cases
6814 -- where typ is Wide_Character and Wide_Wide_Character, the encoding
6815 -- method must cover the entire character range (e.g. UTF-8). But that
6816 -- is a reasonable requirement when dealing with encoded character
6817 -- sequences. Presumably if one of the restrictive encoding mechanisms
6818 -- is in use such as Shift-JIS, then characters that cannot be
6819 -- represented using this encoding will not appear in any case.
6821 when Attribute_Wide_Value
=> Wide_Value
:
6824 Make_Attribute_Reference
(Loc
,
6826 Attribute_Name
=> Name_Value
,
6828 Expressions
=> New_List
(
6829 Make_Function_Call
(Loc
,
6831 New_Occurrence_Of
(RTE
(RE_Wide_String_To_String
), Loc
),
6833 Parameter_Associations
=> New_List
(
6834 Relocate_Node
(First
(Exprs
)),
6835 Make_Integer_Literal
(Loc
,
6836 Intval
=> Int
(Wide_Character_Encoding_Method
)))))));
6838 Analyze_And_Resolve
(N
, Typ
);
6841 ---------------------
6842 -- Wide_Wide_Value --
6843 ---------------------
6845 -- We expand typ'Wide_Value_Value (X) into
6848 -- (Wide_Wide_String_To_String (X, Wide_Character_Encoding_Method))
6850 -- Wide_Wide_String_To_String is a runtime function that converts its
6851 -- wide string argument to String, converting any non-translatable
6852 -- characters into appropriate escape sequences. This preserves the
6853 -- required semantics of Wide_Wide_Value in all cases, and results in a
6854 -- very simple implementation approach.
6856 -- It's not quite right where typ = Wide_Wide_Character, because the
6857 -- encoding method may not cover the whole character type ???
6859 when Attribute_Wide_Wide_Value
=> Wide_Wide_Value
:
6862 Make_Attribute_Reference
(Loc
,
6864 Attribute_Name
=> Name_Value
,
6866 Expressions
=> New_List
(
6867 Make_Function_Call
(Loc
,
6870 (RTE
(RE_Wide_Wide_String_To_String
), Loc
),
6872 Parameter_Associations
=> New_List
(
6873 Relocate_Node
(First
(Exprs
)),
6874 Make_Integer_Literal
(Loc
,
6875 Intval
=> Int
(Wide_Character_Encoding_Method
)))))));
6877 Analyze_And_Resolve
(N
, Typ
);
6878 end Wide_Wide_Value
;
6880 ---------------------
6881 -- Wide_Wide_Width --
6882 ---------------------
6884 -- Wide_Wide_Width attribute is handled in separate unit Exp_Imgv
6886 when Attribute_Wide_Wide_Width
=>
6887 Exp_Imgv
.Expand_Width_Attribute
(N
, Wide_Wide
);
6893 -- Wide_Width attribute is handled in separate unit Exp_Imgv
6895 when Attribute_Wide_Width
=>
6896 Exp_Imgv
.Expand_Width_Attribute
(N
, Wide
);
6902 -- Width attribute is handled in separate unit Exp_Imgv
6904 when Attribute_Width
=>
6905 Exp_Imgv
.Expand_Width_Attribute
(N
, Normal
);
6911 when Attribute_Write
=> Write
: declare
6912 P_Type
: constant Entity_Id
:= Entity
(Pref
);
6913 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
6921 -- If no underlying type, we have an error that will be diagnosed
6922 -- elsewhere, so here we just completely ignore the expansion.
6928 -- Stream operations can appear in user code even if the restriction
6929 -- No_Streams is active (for example, when instantiating a predefined
6930 -- container). In that case rewrite the attribute as a Raise to
6931 -- prevent any run-time use.
6933 if Restriction_Active
(No_Streams
) then
6935 Make_Raise_Program_Error
(Sloc
(N
),
6936 Reason
=> PE_Stream_Operation_Not_Allowed
));
6937 Set_Etype
(N
, U_Type
);
6941 -- The simple case, if there is a TSS for Write, just call it
6943 Pname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Write
);
6945 if Present
(Pname
) then
6949 -- If there is a Stream_Convert pragma, use it, we rewrite
6951 -- sourcetyp'Output (stream, Item)
6955 -- strmtyp'Output (Stream, strmwrite (acttyp (Item)));
6957 -- where strmwrite is the given Write function that converts an
6958 -- argument of type sourcetyp or a type acctyp, from which it is
6959 -- derived to type strmtyp. The conversion to acttyp is required
6960 -- for the derived case.
6962 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
6964 if Present
(Prag
) then
6966 Next
(Next
(First
(Pragma_Argument_Associations
(Prag
))));
6967 Wfunc
:= Entity
(Expression
(Arg3
));
6970 Make_Attribute_Reference
(Loc
,
6971 Prefix
=> New_Occurrence_Of
(Etype
(Wfunc
), Loc
),
6972 Attribute_Name
=> Name_Output
,
6973 Expressions
=> New_List
(
6974 Relocate_Node
(First
(Exprs
)),
6975 Make_Function_Call
(Loc
,
6976 Name
=> New_Occurrence_Of
(Wfunc
, Loc
),
6977 Parameter_Associations
=> New_List
(
6978 OK_Convert_To
(Etype
(First_Formal
(Wfunc
)),
6979 Relocate_Node
(Next
(First
(Exprs
)))))))));
6984 -- For elementary types, we call the W_xxx routine directly
6986 elsif Is_Elementary_Type
(U_Type
) then
6987 Rewrite
(N
, Build_Elementary_Write_Call
(N
));
6993 elsif Is_Array_Type
(U_Type
) then
6994 Build_Array_Write_Procedure
(N
, U_Type
, Decl
, Pname
);
6995 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
6997 -- Tagged type case, use the primitive Write function. Note that
6998 -- this will dispatch in the class-wide case which is what we want
7000 elsif Is_Tagged_Type
(U_Type
) then
7001 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Write
);
7003 -- All other record type cases, including protected records.
7004 -- The latter only arise for expander generated code for
7005 -- handling shared passive partition access.
7009 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
7011 -- Ada 2005 (AI-216): Program_Error is raised when executing
7012 -- the default implementation of the Write attribute of an
7013 -- Unchecked_Union type. However, if the 'Write reference is
7014 -- within the generated Output stream procedure, Write outputs
7015 -- the components, and the default values of the discriminant
7016 -- are streamed by the Output procedure itself.
7018 if Is_Unchecked_Union
(Base_Type
(U_Type
))
7019 and not Is_TSS
(Current_Scope
, TSS_Stream_Output
)
7022 Make_Raise_Program_Error
(Loc
,
7023 Reason
=> PE_Unchecked_Union_Restriction
));
7026 if Has_Discriminants
(U_Type
)
7028 (Discriminant_Default_Value
(First_Discriminant
(U_Type
)))
7030 Build_Mutable_Record_Write_Procedure
7031 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
7033 Build_Record_Write_Procedure
7034 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
7037 Insert_Action
(N
, Decl
);
7041 -- If we fall through, Pname is the procedure to be called
7043 Rewrite_Stream_Proc_Call
(Pname
);
7046 -- Component_Size is handled by the back end, unless the component size
7047 -- is known at compile time, which is always true in the packed array
7048 -- case. It is important that the packed array case is handled in the
7049 -- front end (see Eval_Attribute) since the back end would otherwise get
7050 -- confused by the equivalent packed array type.
7052 when Attribute_Component_Size
=>
7055 -- The following attributes are handled by the back end (except that
7056 -- static cases have already been evaluated during semantic processing,
7057 -- but in any case the back end should not count on this).
7059 -- The back end also handles the non-class-wide cases of Size
7061 when Attribute_Bit_Order |
7062 Attribute_Code_Address |
7063 Attribute_Definite |
7064 Attribute_Null_Parameter |
7065 Attribute_Passed_By_Reference |
7066 Attribute_Pool_Address |
7067 Attribute_Scalar_Storage_Order
=>
7070 -- The following attributes are also handled by the back end, but return
7071 -- a universal integer result, so may need a conversion for checking
7072 -- that the result is in range.
7074 when Attribute_Aft |
7075 Attribute_Max_Alignment_For_Allocation
=>
7076 Apply_Universal_Integer_Attribute_Checks
(N
);
7078 -- The following attributes should not appear at this stage, since they
7079 -- have already been handled by the analyzer (and properly rewritten
7080 -- with corresponding values or entities to represent the right values)
7082 when Attribute_Abort_Signal |
7083 Attribute_Address_Size |
7084 Attribute_Atomic_Always_Lock_Free |
7087 Attribute_Compiler_Version |
7088 Attribute_Default_Bit_Order |
7089 Attribute_Default_Scalar_Storage_Order |
7096 Attribute_Fast_Math |
7097 Attribute_First_Valid |
7098 Attribute_Has_Access_Values |
7099 Attribute_Has_Discriminants |
7100 Attribute_Has_Tagged_Values |
7102 Attribute_Last_Valid |
7103 Attribute_Library_Level |
7104 Attribute_Lock_Free |
7105 Attribute_Machine_Emax |
7106 Attribute_Machine_Emin |
7107 Attribute_Machine_Mantissa |
7108 Attribute_Machine_Overflows |
7109 Attribute_Machine_Radix |
7110 Attribute_Machine_Rounds |
7111 Attribute_Maximum_Alignment |
7112 Attribute_Model_Emin |
7113 Attribute_Model_Epsilon |
7114 Attribute_Model_Mantissa |
7115 Attribute_Model_Small |
7117 Attribute_Partition_ID |
7119 Attribute_Restriction_Set |
7120 Attribute_Safe_Emax |
7121 Attribute_Safe_First |
7122 Attribute_Safe_Large |
7123 Attribute_Safe_Last |
7124 Attribute_Safe_Small |
7126 Attribute_Signed_Zeros |
7128 Attribute_Storage_Unit |
7129 Attribute_Stub_Type |
7130 Attribute_System_Allocator_Alignment |
7131 Attribute_Target_Name |
7132 Attribute_Type_Class |
7133 Attribute_Type_Key |
7134 Attribute_Unconstrained_Array |
7135 Attribute_Universal_Literal_String |
7136 Attribute_Wchar_T_Size |
7137 Attribute_Word_Size
=>
7138 raise Program_Error
;
7140 -- The Asm_Input and Asm_Output attributes are not expanded at this
7141 -- stage, but will be eliminated in the expansion of the Asm call, see
7142 -- Exp_Intr for details. So the back end will never see these either.
7144 when Attribute_Asm_Input |
7145 Attribute_Asm_Output
=>
7149 -- Note: as mentioned earlier, individual sections of the above case
7150 -- statement assume there is no code after the case statement, and are
7151 -- legitimately allowed to execute return statements if they have nothing
7152 -- more to do, so DO NOT add code at this point.
7155 when RE_Not_Available
=>
7157 end Expand_N_Attribute_Reference
;
7159 --------------------------------
7160 -- Expand_Pred_Succ_Attribute --
7161 --------------------------------
7163 -- For typ'Pred (exp), we generate the check
7165 -- [constraint_error when exp = typ'Base'First]
7167 -- Similarly, for typ'Succ (exp), we generate the check
7169 -- [constraint_error when exp = typ'Base'Last]
7171 -- These checks are not generated for modular types, since the proper
7172 -- semantics for Succ and Pred on modular types is to wrap, not raise CE.
7173 -- We also suppress these checks if we are the right side of an assignment
7174 -- statement or the expression of an object declaration, where the flag
7175 -- Suppress_Assignment_Checks is set for the assignment/declaration.
7177 procedure Expand_Pred_Succ_Attribute
(N
: Node_Id
) is
7178 Loc
: constant Source_Ptr
:= Sloc
(N
);
7179 P
: constant Node_Id
:= Parent
(N
);
7183 if Attribute_Name
(N
) = Name_Pred
then
7189 if not Nkind_In
(P
, N_Assignment_Statement
, N_Object_Declaration
)
7190 or else not Suppress_Assignment_Checks
(P
)
7193 Make_Raise_Constraint_Error
(Loc
,
7197 Duplicate_Subexpr_Move_Checks
(First
(Expressions
(N
))),
7199 Make_Attribute_Reference
(Loc
,
7201 New_Occurrence_Of
(Base_Type
(Etype
(Prefix
(N
))), Loc
),
7202 Attribute_Name
=> Cnam
)),
7203 Reason
=> CE_Overflow_Check_Failed
));
7205 end Expand_Pred_Succ_Attribute
;
7207 -----------------------------
7208 -- Expand_Update_Attribute --
7209 -----------------------------
7211 procedure Expand_Update_Attribute
(N
: Node_Id
) is
7212 procedure Process_Component_Or_Element_Update
7217 -- Generate the statements necessary to update a single component or an
7218 -- element of the prefix. The code is inserted before the attribute N.
7219 -- Temp denotes the entity of the anonymous object created to reflect
7220 -- the changes in values. Comp is the component/index expression to be
7221 -- updated. Expr is an expression yielding the new value of Comp. Typ
7222 -- is the type of the prefix of attribute Update.
7224 procedure Process_Range_Update
7229 -- Generate the statements necessary to update a slice of the prefix.
7230 -- The code is inserted before the attribute N. Temp denotes the entity
7231 -- of the anonymous object created to reflect the changes in values.
7232 -- Comp is range of the slice to be updated. Expr is an expression
7233 -- yielding the new value of Comp. Typ is the type of the prefix of
7234 -- attribute Update.
7236 -----------------------------------------
7237 -- Process_Component_Or_Element_Update --
7238 -----------------------------------------
7240 procedure Process_Component_Or_Element_Update
7246 Loc
: constant Source_Ptr
:= Sloc
(Comp
);
7251 -- An array element may be modified by the following relations
7252 -- depending on the number of dimensions:
7254 -- 1 => Expr -- one dimensional update
7255 -- (1, ..., N) => Expr -- multi dimensional update
7257 -- The above forms are converted in assignment statements where the
7258 -- left hand side is an indexed component:
7260 -- Temp (1) := Expr; -- one dimensional update
7261 -- Temp (1, ..., N) := Expr; -- multi dimensional update
7263 if Is_Array_Type
(Typ
) then
7265 -- The index expressions of a multi dimensional array update
7266 -- appear as an aggregate.
7268 if Nkind
(Comp
) = N_Aggregate
then
7269 Exprs
:= New_Copy_List_Tree
(Expressions
(Comp
));
7271 Exprs
:= New_List
(Relocate_Node
(Comp
));
7275 Make_Indexed_Component
(Loc
,
7276 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
7277 Expressions
=> Exprs
);
7279 -- A record component update appears in the following form:
7283 -- The above relation is transformed into an assignment statement
7284 -- where the left hand side is a selected component:
7286 -- Temp.Comp := Expr;
7288 else pragma Assert
(Is_Record_Type
(Typ
));
7290 Make_Selected_Component
(Loc
,
7291 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
7292 Selector_Name
=> Relocate_Node
(Comp
));
7296 Make_Assignment_Statement
(Loc
,
7298 Expression
=> Relocate_Node
(Expr
)));
7299 end Process_Component_Or_Element_Update
;
7301 --------------------------
7302 -- Process_Range_Update --
7303 --------------------------
7305 procedure Process_Range_Update
7311 Index_Typ
: constant Entity_Id
:= Etype
(First_Index
(Typ
));
7312 Loc
: constant Source_Ptr
:= Sloc
(Comp
);
7316 -- A range update appears as
7318 -- (Low .. High => Expr)
7320 -- The above construct is transformed into a loop that iterates over
7321 -- the given range and modifies the corresponding array values to the
7324 -- for Index in Low .. High loop
7325 -- Temp (<Index_Typ> (Index)) := Expr;
7328 Index
:= Make_Temporary
(Loc
, 'I');
7331 Make_Loop_Statement
(Loc
,
7333 Make_Iteration_Scheme
(Loc
,
7334 Loop_Parameter_Specification
=>
7335 Make_Loop_Parameter_Specification
(Loc
,
7336 Defining_Identifier
=> Index
,
7337 Discrete_Subtype_Definition
=> Relocate_Node
(Comp
))),
7339 Statements
=> New_List
(
7340 Make_Assignment_Statement
(Loc
,
7342 Make_Indexed_Component
(Loc
,
7343 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
7344 Expressions
=> New_List
(
7345 Convert_To
(Index_Typ
,
7346 New_Occurrence_Of
(Index
, Loc
)))),
7347 Expression
=> Relocate_Node
(Expr
))),
7349 End_Label
=> Empty
));
7350 end Process_Range_Update
;
7354 Aggr
: constant Node_Id
:= First
(Expressions
(N
));
7355 Loc
: constant Source_Ptr
:= Sloc
(N
);
7356 Pref
: constant Node_Id
:= Prefix
(N
);
7357 Typ
: constant Entity_Id
:= Etype
(Pref
);
7363 -- Start of processing for Expand_Update_Attribute
7366 -- Create the anonymous object that stores the value of the prefix and
7367 -- reflects subsequent changes in value. Generate:
7369 -- Temp : <type of Pref> := Pref;
7371 Temp
:= Make_Temporary
(Loc
, 'T');
7374 Make_Object_Declaration
(Loc
,
7375 Defining_Identifier
=> Temp
,
7376 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
7377 Expression
=> Relocate_Node
(Pref
)));
7379 -- Process the update aggregate
7381 Assoc
:= First
(Component_Associations
(Aggr
));
7382 while Present
(Assoc
) loop
7383 Comp
:= First
(Choices
(Assoc
));
7384 Expr
:= Expression
(Assoc
);
7385 while Present
(Comp
) loop
7386 if Nkind
(Comp
) = N_Range
then
7387 Process_Range_Update
(Temp
, Comp
, Expr
, Typ
);
7389 Process_Component_Or_Element_Update
(Temp
, Comp
, Expr
, Typ
);
7398 -- The attribute is replaced by a reference to the anonymous object
7400 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
7402 end Expand_Update_Attribute
;
7408 procedure Find_Fat_Info
7410 Fat_Type
: out Entity_Id
;
7411 Fat_Pkg
: out RE_Id
)
7413 Rtyp
: constant Entity_Id
:= Root_Type
(T
);
7416 -- All we do is use the root type (historically this dealt with
7417 -- VAX-float .. to be cleaned up further later ???)
7421 if Fat_Type
= Standard_Short_Float
then
7422 Fat_Pkg
:= RE_Attr_Short_Float
;
7424 elsif Fat_Type
= Standard_Float
then
7425 Fat_Pkg
:= RE_Attr_Float
;
7427 elsif Fat_Type
= Standard_Long_Float
then
7428 Fat_Pkg
:= RE_Attr_Long_Float
;
7430 elsif Fat_Type
= Standard_Long_Long_Float
then
7431 Fat_Pkg
:= RE_Attr_Long_Long_Float
;
7433 -- Universal real (which is its own root type) is treated as being
7434 -- equivalent to Standard.Long_Long_Float, since it is defined to
7435 -- have the same precision as the longest Float type.
7437 elsif Fat_Type
= Universal_Real
then
7438 Fat_Type
:= Standard_Long_Long_Float
;
7439 Fat_Pkg
:= RE_Attr_Long_Long_Float
;
7442 raise Program_Error
;
7446 ----------------------------
7447 -- Find_Stream_Subprogram --
7448 ----------------------------
7450 function Find_Stream_Subprogram
7452 Nam
: TSS_Name_Type
) return Entity_Id
7454 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
7455 Ent
: constant Entity_Id
:= TSS
(Typ
, Nam
);
7457 function Is_Available
(Entity
: RE_Id
) return Boolean;
7458 pragma Inline
(Is_Available
);
7459 -- Function to check whether the specified run-time call is available
7460 -- in the run time used. In the case of a configurable run time, it
7461 -- is normal that some subprograms are not there.
7463 -- I don't understand this routine at all, why is this not just a
7464 -- call to RTE_Available? And if for some reason we need a different
7465 -- routine with different semantics, why is not in Rtsfind ???
7471 function Is_Available
(Entity
: RE_Id
) return Boolean is
7473 -- Assume that the unit will always be available when using a
7474 -- "normal" (not configurable) run time.
7476 return not Configurable_Run_Time_Mode
or else RTE_Available
(Entity
);
7479 -- Start of processing for Find_Stream_Subprogram
7482 if Present
(Ent
) then
7486 -- Stream attributes for strings are expanded into library calls. The
7487 -- following checks are disabled when the run-time is not available or
7488 -- when compiling predefined types due to bootstrap issues. As a result,
7489 -- the compiler will generate in-place stream routines for string types
7490 -- that appear in GNAT's library, but will generate calls via rtsfind
7491 -- to library routines for user code.
7493 -- ??? For now, disable this code for JVM, since this generates a
7494 -- VerifyError exception at run time on e.g. c330001.
7496 -- This is disabled for AAMP, to avoid creating dependences on files not
7497 -- supported in the AAMP library (such as s-fileio.adb).
7499 -- Note: In the case of using a configurable run time, it is very likely
7500 -- that stream routines for string types are not present (they require
7501 -- file system support). In this case, the specific stream routines for
7502 -- strings are not used, relying on the regular stream mechanism
7503 -- instead. That is why we include the test Is_Available when dealing
7504 -- with these cases.
7506 if VM_Target
/= JVM_Target
7507 and then not AAMP_On_Target
7509 not Is_Predefined_File_Name
(Unit_File_Name
(Current_Sem_Unit
))
7511 -- Storage_Array as defined in package System.Storage_Elements
7513 if Is_RTE
(Base_Typ
, RE_Storage_Array
) then
7515 -- Case of No_Stream_Optimizations restriction active
7517 if Restriction_Active
(No_Stream_Optimizations
) then
7518 if Nam
= TSS_Stream_Input
7519 and then Is_Available
(RE_Storage_Array_Input
)
7521 return RTE
(RE_Storage_Array_Input
);
7523 elsif Nam
= TSS_Stream_Output
7524 and then Is_Available
(RE_Storage_Array_Output
)
7526 return RTE
(RE_Storage_Array_Output
);
7528 elsif Nam
= TSS_Stream_Read
7529 and then Is_Available
(RE_Storage_Array_Read
)
7531 return RTE
(RE_Storage_Array_Read
);
7533 elsif Nam
= TSS_Stream_Write
7534 and then Is_Available
(RE_Storage_Array_Write
)
7536 return RTE
(RE_Storage_Array_Write
);
7538 elsif Nam
/= TSS_Stream_Input
and then
7539 Nam
/= TSS_Stream_Output
and then
7540 Nam
/= TSS_Stream_Read
and then
7541 Nam
/= TSS_Stream_Write
7543 raise Program_Error
;
7546 -- Restriction No_Stream_Optimizations is not set, so we can go
7547 -- ahead and optimize using the block IO forms of the routines.
7550 if Nam
= TSS_Stream_Input
7551 and then Is_Available
(RE_Storage_Array_Input_Blk_IO
)
7553 return RTE
(RE_Storage_Array_Input_Blk_IO
);
7555 elsif Nam
= TSS_Stream_Output
7556 and then Is_Available
(RE_Storage_Array_Output_Blk_IO
)
7558 return RTE
(RE_Storage_Array_Output_Blk_IO
);
7560 elsif Nam
= TSS_Stream_Read
7561 and then Is_Available
(RE_Storage_Array_Read_Blk_IO
)
7563 return RTE
(RE_Storage_Array_Read_Blk_IO
);
7565 elsif Nam
= TSS_Stream_Write
7566 and then Is_Available
(RE_Storage_Array_Write_Blk_IO
)
7568 return RTE
(RE_Storage_Array_Write_Blk_IO
);
7570 elsif Nam
/= TSS_Stream_Input
and then
7571 Nam
/= TSS_Stream_Output
and then
7572 Nam
/= TSS_Stream_Read
and then
7573 Nam
/= TSS_Stream_Write
7575 raise Program_Error
;
7579 -- Stream_Element_Array as defined in package Ada.Streams
7581 elsif Is_RTE
(Base_Typ
, RE_Stream_Element_Array
) then
7583 -- Case of No_Stream_Optimizations restriction active
7585 if Restriction_Active
(No_Stream_Optimizations
) then
7586 if Nam
= TSS_Stream_Input
7587 and then Is_Available
(RE_Stream_Element_Array_Input
)
7589 return RTE
(RE_Stream_Element_Array_Input
);
7591 elsif Nam
= TSS_Stream_Output
7592 and then Is_Available
(RE_Stream_Element_Array_Output
)
7594 return RTE
(RE_Stream_Element_Array_Output
);
7596 elsif Nam
= TSS_Stream_Read
7597 and then Is_Available
(RE_Stream_Element_Array_Read
)
7599 return RTE
(RE_Stream_Element_Array_Read
);
7601 elsif Nam
= TSS_Stream_Write
7602 and then Is_Available
(RE_Stream_Element_Array_Write
)
7604 return RTE
(RE_Stream_Element_Array_Write
);
7606 elsif Nam
/= TSS_Stream_Input
and then
7607 Nam
/= TSS_Stream_Output
and then
7608 Nam
/= TSS_Stream_Read
and then
7609 Nam
/= TSS_Stream_Write
7611 raise Program_Error
;
7614 -- Restriction No_Stream_Optimizations is not set, so we can go
7615 -- ahead and optimize using the block IO forms of the routines.
7618 if Nam
= TSS_Stream_Input
7619 and then Is_Available
(RE_Stream_Element_Array_Input_Blk_IO
)
7621 return RTE
(RE_Stream_Element_Array_Input_Blk_IO
);
7623 elsif Nam
= TSS_Stream_Output
7624 and then Is_Available
(RE_Stream_Element_Array_Output_Blk_IO
)
7626 return RTE
(RE_Stream_Element_Array_Output_Blk_IO
);
7628 elsif Nam
= TSS_Stream_Read
7629 and then Is_Available
(RE_Stream_Element_Array_Read_Blk_IO
)
7631 return RTE
(RE_Stream_Element_Array_Read_Blk_IO
);
7633 elsif Nam
= TSS_Stream_Write
7634 and then Is_Available
(RE_Stream_Element_Array_Write_Blk_IO
)
7636 return RTE
(RE_Stream_Element_Array_Write_Blk_IO
);
7638 elsif Nam
/= TSS_Stream_Input
and then
7639 Nam
/= TSS_Stream_Output
and then
7640 Nam
/= TSS_Stream_Read
and then
7641 Nam
/= TSS_Stream_Write
7643 raise Program_Error
;
7647 -- String as defined in package Ada
7649 elsif Base_Typ
= Standard_String
then
7651 -- Case of No_Stream_Optimizations restriction active
7653 if Restriction_Active
(No_Stream_Optimizations
) then
7654 if Nam
= TSS_Stream_Input
7655 and then Is_Available
(RE_String_Input
)
7657 return RTE
(RE_String_Input
);
7659 elsif Nam
= TSS_Stream_Output
7660 and then Is_Available
(RE_String_Output
)
7662 return RTE
(RE_String_Output
);
7664 elsif Nam
= TSS_Stream_Read
7665 and then Is_Available
(RE_String_Read
)
7667 return RTE
(RE_String_Read
);
7669 elsif Nam
= TSS_Stream_Write
7670 and then Is_Available
(RE_String_Write
)
7672 return RTE
(RE_String_Write
);
7674 elsif Nam
/= TSS_Stream_Input
and then
7675 Nam
/= TSS_Stream_Output
and then
7676 Nam
/= TSS_Stream_Read
and then
7677 Nam
/= TSS_Stream_Write
7679 raise Program_Error
;
7682 -- Restriction No_Stream_Optimizations is not set, so we can go
7683 -- ahead and optimize using the block IO forms of the routines.
7686 if Nam
= TSS_Stream_Input
7687 and then Is_Available
(RE_String_Input_Blk_IO
)
7689 return RTE
(RE_String_Input_Blk_IO
);
7691 elsif Nam
= TSS_Stream_Output
7692 and then Is_Available
(RE_String_Output_Blk_IO
)
7694 return RTE
(RE_String_Output_Blk_IO
);
7696 elsif Nam
= TSS_Stream_Read
7697 and then Is_Available
(RE_String_Read_Blk_IO
)
7699 return RTE
(RE_String_Read_Blk_IO
);
7701 elsif Nam
= TSS_Stream_Write
7702 and then Is_Available
(RE_String_Write_Blk_IO
)
7704 return RTE
(RE_String_Write_Blk_IO
);
7706 elsif Nam
/= TSS_Stream_Input
and then
7707 Nam
/= TSS_Stream_Output
and then
7708 Nam
/= TSS_Stream_Read
and then
7709 Nam
/= TSS_Stream_Write
7711 raise Program_Error
;
7715 -- Wide_String as defined in package Ada
7717 elsif Base_Typ
= Standard_Wide_String
then
7719 -- Case of No_Stream_Optimizations restriction active
7721 if Restriction_Active
(No_Stream_Optimizations
) then
7722 if Nam
= TSS_Stream_Input
7723 and then Is_Available
(RE_Wide_String_Input
)
7725 return RTE
(RE_Wide_String_Input
);
7727 elsif Nam
= TSS_Stream_Output
7728 and then Is_Available
(RE_Wide_String_Output
)
7730 return RTE
(RE_Wide_String_Output
);
7732 elsif Nam
= TSS_Stream_Read
7733 and then Is_Available
(RE_Wide_String_Read
)
7735 return RTE
(RE_Wide_String_Read
);
7737 elsif Nam
= TSS_Stream_Write
7738 and then Is_Available
(RE_Wide_String_Write
)
7740 return RTE
(RE_Wide_String_Write
);
7742 elsif Nam
/= TSS_Stream_Input
and then
7743 Nam
/= TSS_Stream_Output
and then
7744 Nam
/= TSS_Stream_Read
and then
7745 Nam
/= TSS_Stream_Write
7747 raise Program_Error
;
7750 -- Restriction No_Stream_Optimizations is not set, so we can go
7751 -- ahead and optimize using the block IO forms of the routines.
7754 if Nam
= TSS_Stream_Input
7755 and then Is_Available
(RE_Wide_String_Input_Blk_IO
)
7757 return RTE
(RE_Wide_String_Input_Blk_IO
);
7759 elsif Nam
= TSS_Stream_Output
7760 and then Is_Available
(RE_Wide_String_Output_Blk_IO
)
7762 return RTE
(RE_Wide_String_Output_Blk_IO
);
7764 elsif Nam
= TSS_Stream_Read
7765 and then Is_Available
(RE_Wide_String_Read_Blk_IO
)
7767 return RTE
(RE_Wide_String_Read_Blk_IO
);
7769 elsif Nam
= TSS_Stream_Write
7770 and then Is_Available
(RE_Wide_String_Write_Blk_IO
)
7772 return RTE
(RE_Wide_String_Write_Blk_IO
);
7774 elsif Nam
/= TSS_Stream_Input
and then
7775 Nam
/= TSS_Stream_Output
and then
7776 Nam
/= TSS_Stream_Read
and then
7777 Nam
/= TSS_Stream_Write
7779 raise Program_Error
;
7783 -- Wide_Wide_String as defined in package Ada
7785 elsif Base_Typ
= Standard_Wide_Wide_String
then
7787 -- Case of No_Stream_Optimizations restriction active
7789 if Restriction_Active
(No_Stream_Optimizations
) then
7790 if Nam
= TSS_Stream_Input
7791 and then Is_Available
(RE_Wide_Wide_String_Input
)
7793 return RTE
(RE_Wide_Wide_String_Input
);
7795 elsif Nam
= TSS_Stream_Output
7796 and then Is_Available
(RE_Wide_Wide_String_Output
)
7798 return RTE
(RE_Wide_Wide_String_Output
);
7800 elsif Nam
= TSS_Stream_Read
7801 and then Is_Available
(RE_Wide_Wide_String_Read
)
7803 return RTE
(RE_Wide_Wide_String_Read
);
7805 elsif Nam
= TSS_Stream_Write
7806 and then Is_Available
(RE_Wide_Wide_String_Write
)
7808 return RTE
(RE_Wide_Wide_String_Write
);
7810 elsif Nam
/= TSS_Stream_Input
and then
7811 Nam
/= TSS_Stream_Output
and then
7812 Nam
/= TSS_Stream_Read
and then
7813 Nam
/= TSS_Stream_Write
7815 raise Program_Error
;
7818 -- Restriction No_Stream_Optimizations is not set, so we can go
7819 -- ahead and optimize using the block IO forms of the routines.
7822 if Nam
= TSS_Stream_Input
7823 and then Is_Available
(RE_Wide_Wide_String_Input_Blk_IO
)
7825 return RTE
(RE_Wide_Wide_String_Input_Blk_IO
);
7827 elsif Nam
= TSS_Stream_Output
7828 and then Is_Available
(RE_Wide_Wide_String_Output_Blk_IO
)
7830 return RTE
(RE_Wide_Wide_String_Output_Blk_IO
);
7832 elsif Nam
= TSS_Stream_Read
7833 and then Is_Available
(RE_Wide_Wide_String_Read_Blk_IO
)
7835 return RTE
(RE_Wide_Wide_String_Read_Blk_IO
);
7837 elsif Nam
= TSS_Stream_Write
7838 and then Is_Available
(RE_Wide_Wide_String_Write_Blk_IO
)
7840 return RTE
(RE_Wide_Wide_String_Write_Blk_IO
);
7842 elsif Nam
/= TSS_Stream_Input
and then
7843 Nam
/= TSS_Stream_Output
and then
7844 Nam
/= TSS_Stream_Read
and then
7845 Nam
/= TSS_Stream_Write
7847 raise Program_Error
;
7853 if Is_Tagged_Type
(Typ
) and then Is_Derived_Type
(Typ
) then
7854 return Find_Prim_Op
(Typ
, Nam
);
7856 return Find_Inherited_TSS
(Typ
, Nam
);
7858 end Find_Stream_Subprogram
;
7864 function Full_Base
(T
: Entity_Id
) return Entity_Id
is
7868 BT
:= Base_Type
(T
);
7870 if Is_Private_Type
(BT
)
7871 and then Present
(Full_View
(BT
))
7873 BT
:= Full_View
(BT
);
7879 -----------------------
7880 -- Get_Index_Subtype --
7881 -----------------------
7883 function Get_Index_Subtype
(N
: Node_Id
) return Node_Id
is
7884 P_Type
: Entity_Id
:= Etype
(Prefix
(N
));
7889 if Is_Access_Type
(P_Type
) then
7890 P_Type
:= Designated_Type
(P_Type
);
7893 if No
(Expressions
(N
)) then
7896 J
:= UI_To_Int
(Expr_Value
(First
(Expressions
(N
))));
7899 Indx
:= First_Index
(P_Type
);
7905 return Etype
(Indx
);
7906 end Get_Index_Subtype
;
7908 -------------------------------
7909 -- Get_Stream_Convert_Pragma --
7910 -------------------------------
7912 function Get_Stream_Convert_Pragma
(T
: Entity_Id
) return Node_Id
is
7917 -- Note: we cannot use Get_Rep_Pragma here because of the peculiarity
7918 -- that a stream convert pragma for a tagged type is not inherited from
7919 -- its parent. Probably what is wrong here is that it is basically
7920 -- incorrect to consider a stream convert pragma to be a representation
7921 -- pragma at all ???
7923 N
:= First_Rep_Item
(Implementation_Base_Type
(T
));
7924 while Present
(N
) loop
7925 if Nkind
(N
) = N_Pragma
7926 and then Pragma_Name
(N
) = Name_Stream_Convert
7928 -- For tagged types this pragma is not inherited, so we
7929 -- must verify that it is defined for the given type and
7933 Entity
(Expression
(First
(Pragma_Argument_Associations
(N
))));
7935 if not Is_Tagged_Type
(T
)
7937 or else (Is_Private_Type
(Typ
) and then T
= Full_View
(Typ
))
7947 end Get_Stream_Convert_Pragma
;
7949 ---------------------------------
7950 -- Is_Constrained_Packed_Array --
7951 ---------------------------------
7953 function Is_Constrained_Packed_Array
(Typ
: Entity_Id
) return Boolean is
7954 Arr
: Entity_Id
:= Typ
;
7957 if Is_Access_Type
(Arr
) then
7958 Arr
:= Designated_Type
(Arr
);
7961 return Is_Array_Type
(Arr
)
7962 and then Is_Constrained
(Arr
)
7963 and then Present
(Packed_Array_Impl_Type
(Arr
));
7964 end Is_Constrained_Packed_Array
;
7966 ----------------------------------------
7967 -- Is_Inline_Floating_Point_Attribute --
7968 ----------------------------------------
7970 function Is_Inline_Floating_Point_Attribute
(N
: Node_Id
) return Boolean is
7971 Id
: constant Attribute_Id
:= Get_Attribute_Id
(Attribute_Name
(N
));
7973 function Is_GCC_Target
return Boolean;
7974 -- Return True if we are using a GCC target/back-end
7975 -- ??? Note: the implementation is kludgy/fragile
7981 function Is_GCC_Target
return Boolean is
7983 return VM_Target
= No_VM
and then not CodePeer_Mode
7984 and then not AAMP_On_Target
;
7987 -- Start of processing for Exp_Attr
7990 -- Machine and Model can be expanded by the GCC backend only
7992 if Id
= Attribute_Machine
or else Id
= Attribute_Model
then
7993 return Is_GCC_Target
;
7995 -- Remaining cases handled by all back ends are Rounding and Truncation
7996 -- when appearing as the operand of a conversion to some integer type.
7998 elsif Nkind
(Parent
(N
)) /= N_Type_Conversion
7999 or else not Is_Integer_Type
(Etype
(Parent
(N
)))
8004 -- Here we are in the integer conversion context
8006 -- Very probably we should also recognize the cases of Machine_Rounding
8007 -- and unbiased rounding in this conversion context, but the back end is
8008 -- not yet prepared to handle these cases ???
8010 return Id
= Attribute_Rounding
or else Id
= Attribute_Truncation
;
8011 end Is_Inline_Floating_Point_Attribute
;