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 Atree
; use Atree
;
27 with Checks
; use Checks
;
28 with Einfo
; use Einfo
;
29 with Elists
; use Elists
;
30 with Exp_Atag
; use Exp_Atag
;
31 with Exp_Ch2
; use Exp_Ch2
;
32 with Exp_Ch3
; use Exp_Ch3
;
33 with Exp_Ch6
; use Exp_Ch6
;
34 with Exp_Ch9
; use Exp_Ch9
;
35 with Exp_Dist
; use Exp_Dist
;
36 with Exp_Imgv
; use Exp_Imgv
;
37 with Exp_Pakd
; use Exp_Pakd
;
38 with Exp_Strm
; use Exp_Strm
;
39 with Exp_Tss
; use Exp_Tss
;
40 with Exp_Util
; use Exp_Util
;
41 with Fname
; use Fname
;
42 with Freeze
; use Freeze
;
43 with Gnatvsn
; use Gnatvsn
;
44 with Itypes
; use Itypes
;
46 with Namet
; use Namet
;
47 with Nmake
; use Nmake
;
48 with Nlists
; use Nlists
;
50 with Restrict
; use Restrict
;
51 with Rident
; use Rident
;
52 with Rtsfind
; use Rtsfind
;
54 with Sem_Aux
; use Sem_Aux
;
55 with Sem_Ch6
; use Sem_Ch6
;
56 with Sem_Ch7
; use Sem_Ch7
;
57 with Sem_Ch8
; use Sem_Ch8
;
58 with Sem_Eval
; use Sem_Eval
;
59 with Sem_Res
; use Sem_Res
;
60 with Sem_Util
; use Sem_Util
;
61 with Sinfo
; use Sinfo
;
62 with Snames
; use Snames
;
63 with Stand
; use Stand
;
64 with Stringt
; use Stringt
;
65 with Targparm
; use Targparm
;
66 with Tbuild
; use Tbuild
;
67 with Ttypes
; use Ttypes
;
68 with Uintp
; use Uintp
;
69 with Uname
; use Uname
;
70 with Validsw
; use Validsw
;
72 package body Exp_Attr
is
74 -----------------------
75 -- Local Subprograms --
76 -----------------------
78 function Build_Array_VS_Func
80 Nod
: Node_Id
) return Entity_Id
;
81 -- Build function to test Valid_Scalars for array type A_Type. Nod is the
82 -- Valid_Scalars attribute node, used to insert the function body, and the
83 -- value returned is the entity of the constructed function body. We do not
84 -- bother to generate a separate spec for this subprogram.
86 function Build_Record_VS_Func
88 Nod
: Node_Id
) return Entity_Id
;
89 -- Build function to test Valid_Scalars for record type A_Type. Nod is the
90 -- Valid_Scalars attribute node, used to insert the function body, and the
91 -- value returned is the entity of the constructed function body. We do not
92 -- bother to generate a separate spec for this subprogram.
94 procedure Compile_Stream_Body_In_Scope
99 -- The body for a stream subprogram may be generated outside of the scope
100 -- of the type. If the type is fully private, it may depend on the full
101 -- view of other types (e.g. indexes) that are currently private as well.
102 -- We install the declarations of the package in which the type is declared
103 -- before compiling the body in what is its proper environment. The Check
104 -- parameter indicates if checks are to be suppressed for the stream body.
105 -- We suppress checks for array/record reads, since the rule is that these
106 -- are like assignments, out of range values due to uninitialized storage,
107 -- or other invalid values do NOT cause a Constraint_Error to be raised.
108 -- If we are within an instance body all visibility has been established
109 -- already and there is no need to install the package.
111 procedure Expand_Access_To_Protected_Op
115 -- An attribute reference to a protected subprogram is transformed into
116 -- a pair of pointers: one to the object, and one to the operations.
117 -- This expansion is performed for 'Access and for 'Unrestricted_Access.
119 procedure Expand_Fpt_Attribute
124 -- This procedure expands a call to a floating-point attribute function.
125 -- N is the attribute reference node, and Args is a list of arguments to
126 -- be passed to the function call. Pkg identifies the package containing
127 -- the appropriate instantiation of System.Fat_Gen. Float arguments in Args
128 -- have already been converted to the floating-point type for which Pkg was
129 -- instantiated. The Nam argument is the relevant attribute processing
130 -- routine to be called. This is the same as the attribute name, except in
131 -- the Unaligned_Valid case.
133 procedure Expand_Fpt_Attribute_R
(N
: Node_Id
);
134 -- This procedure expands a call to a floating-point attribute function
135 -- that takes a single floating-point argument. The function to be called
136 -- is always the same as the attribute name.
138 procedure Expand_Fpt_Attribute_RI
(N
: Node_Id
);
139 -- This procedure expands a call to a floating-point attribute function
140 -- that takes one floating-point argument and one integer argument. The
141 -- function to be called is always the same as the attribute name.
143 procedure Expand_Fpt_Attribute_RR
(N
: Node_Id
);
144 -- This procedure expands a call to a floating-point attribute function
145 -- that takes two floating-point arguments. The function to be called
146 -- is always the same as the attribute name.
148 procedure Expand_Loop_Entry_Attribute
(N
: Node_Id
);
149 -- Handle the expansion of attribute 'Loop_Entry. As a result, the related
150 -- loop may be converted into a conditional block. See body for details.
152 procedure Expand_Min_Max_Attribute
(N
: Node_Id
);
153 -- Handle the expansion of attributes 'Max and 'Min, including expanding
154 -- then out if we are in Modify_Tree_For_C mode.
156 procedure Expand_Pred_Succ_Attribute
(N
: Node_Id
);
157 -- Handles expansion of Pred or Succ attributes for case of non-real
158 -- operand with overflow checking required.
160 procedure Expand_Update_Attribute
(N
: Node_Id
);
161 -- Handle the expansion of attribute Update
163 function Get_Index_Subtype
(N
: Node_Id
) return Entity_Id
;
164 -- Used for Last, Last, and Length, when the prefix is an array type.
165 -- Obtains the corresponding index subtype.
167 procedure Find_Fat_Info
169 Fat_Type
: out Entity_Id
;
170 Fat_Pkg
: out RE_Id
);
171 -- Given a floating-point type T, identifies the package containing the
172 -- attributes for this type (returned in Fat_Pkg), and the corresponding
173 -- type for which this package was instantiated from Fat_Gen. Error if T
174 -- is not a floating-point type.
176 function Find_Stream_Subprogram
178 Nam
: TSS_Name_Type
) return Entity_Id
;
179 -- Returns the stream-oriented subprogram attribute for Typ. For tagged
180 -- types, the corresponding primitive operation is looked up, else the
181 -- appropriate TSS from the type itself, or from its closest ancestor
182 -- defining it, is returned. In both cases, inheritance of representation
183 -- aspects is thus taken into account.
185 function Full_Base
(T
: Entity_Id
) return Entity_Id
;
186 -- The stream functions need to examine the underlying representation of
187 -- composite types. In some cases T may be non-private but its base type
188 -- is, in which case the function returns the corresponding full view.
190 function Get_Stream_Convert_Pragma
(T
: Entity_Id
) return Node_Id
;
191 -- Given a type, find a corresponding stream convert pragma that applies to
192 -- the implementation base type of this type (Typ). If found, return the
193 -- pragma node, otherwise return Empty if no pragma is found.
195 function Is_Constrained_Packed_Array
(Typ
: Entity_Id
) return Boolean;
196 -- Utility for array attributes, returns true on packed constrained
197 -- arrays, and on access to same.
199 function Is_Inline_Floating_Point_Attribute
(N
: Node_Id
) return Boolean;
200 -- Returns true iff the given node refers to an attribute call that
201 -- can be expanded directly by the back end and does not need front end
202 -- expansion. Typically used for rounding and truncation attributes that
203 -- appear directly inside a conversion to integer.
205 -------------------------
206 -- Build_Array_VS_Func --
207 -------------------------
209 function Build_Array_VS_Func
211 Nod
: Node_Id
) return Entity_Id
213 Loc
: constant Source_Ptr
:= Sloc
(Nod
);
214 Func_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
215 Comp_Type
: constant Entity_Id
:= Component_Type
(A_Type
);
216 Body_Stmts
: List_Id
;
217 Index_List
: List_Id
;
220 function Test_Component
return List_Id
;
221 -- Create one statement to test validity of one component designated by
222 -- a full set of indexes. Returns statement list containing test.
224 function Test_One_Dimension
(N
: Int
) return List_Id
;
225 -- Create loop to test one dimension of the array. The single statement
226 -- in the loop body tests the inner dimensions if any, or else the
227 -- single component. Note that this procedure is called recursively,
228 -- with N being the dimension to be initialized. A call with N greater
229 -- than the number of dimensions simply generates the component test,
230 -- terminating the recursion. Returns statement list containing tests.
236 function Test_Component
return List_Id
is
242 Make_Indexed_Component
(Loc
,
243 Prefix
=> Make_Identifier
(Loc
, Name_uA
),
244 Expressions
=> Index_List
);
246 if Is_Scalar_Type
(Comp_Type
) then
249 Anam
:= Name_Valid_Scalars
;
253 Make_If_Statement
(Loc
,
257 Make_Attribute_Reference
(Loc
,
258 Attribute_Name
=> Anam
,
260 Then_Statements
=> New_List
(
261 Make_Simple_Return_Statement
(Loc
,
262 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
)))));
265 ------------------------
266 -- Test_One_Dimension --
267 ------------------------
269 function Test_One_Dimension
(N
: Int
) return List_Id
is
273 -- If all dimensions dealt with, we simply test the component
275 if N
> Number_Dimensions
(A_Type
) then
276 return Test_Component
;
278 -- Here we generate the required loop
282 Make_Defining_Identifier
(Loc
, New_External_Name
('J', N
));
284 Append
(New_Occurrence_Of
(Index
, Loc
), Index_List
);
287 Make_Implicit_Loop_Statement
(Nod
,
290 Make_Iteration_Scheme
(Loc
,
291 Loop_Parameter_Specification
=>
292 Make_Loop_Parameter_Specification
(Loc
,
293 Defining_Identifier
=> Index
,
294 Discrete_Subtype_Definition
=>
295 Make_Attribute_Reference
(Loc
,
296 Prefix
=> Make_Identifier
(Loc
, Name_uA
),
297 Attribute_Name
=> Name_Range
,
298 Expressions
=> New_List
(
299 Make_Integer_Literal
(Loc
, N
))))),
300 Statements
=> Test_One_Dimension
(N
+ 1)),
301 Make_Simple_Return_Statement
(Loc
,
302 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
304 end Test_One_Dimension
;
306 -- Start of processing for Build_Array_VS_Func
309 Index_List
:= New_List
;
310 Body_Stmts
:= Test_One_Dimension
(1);
312 -- Parameter is always (A : A_Typ)
314 Formals
:= New_List
(
315 Make_Parameter_Specification
(Loc
,
316 Defining_Identifier
=> Make_Defining_Identifier
(Loc
, Name_uA
),
318 Out_Present
=> False,
319 Parameter_Type
=> New_Occurrence_Of
(A_Type
, Loc
)));
323 Set_Ekind
(Func_Id
, E_Function
);
324 Set_Is_Internal
(Func_Id
);
327 Make_Subprogram_Body
(Loc
,
329 Make_Function_Specification
(Loc
,
330 Defining_Unit_Name
=> Func_Id
,
331 Parameter_Specifications
=> Formals
,
333 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
334 Declarations
=> New_List
,
335 Handled_Statement_Sequence
=>
336 Make_Handled_Sequence_Of_Statements
(Loc
,
337 Statements
=> Body_Stmts
)));
339 if not Debug_Generated_Code
then
340 Set_Debug_Info_Off
(Func_Id
);
343 Set_Is_Pure
(Func_Id
);
345 end Build_Array_VS_Func
;
347 --------------------------
348 -- Build_Record_VS_Func --
349 --------------------------
353 -- function _Valid_Scalars (X : T) return Boolean is
355 -- -- Check discriminants
357 -- if not X.D1'Valid_Scalars or else
358 -- not X.D2'Valid_Scalars or else
364 -- -- Check components
366 -- if not X.C1'Valid_Scalars or else
367 -- not X.C2'Valid_Scalars or else
373 -- -- Check variant part
377 -- if not X.C2'Valid_Scalars or else
378 -- not X.C3'Valid_Scalars or else
385 -- if not X.Cn'Valid_Scalars or else
393 -- end _Valid_Scalars;
395 function Build_Record_VS_Func
397 Nod
: Node_Id
) return Entity_Id
399 Loc
: constant Source_Ptr
:= Sloc
(R_Type
);
400 Func_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
401 X
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_X
);
403 function Make_VS_Case
406 Discrs
: Elist_Id
:= New_Elmt_List
) return List_Id
;
407 -- Building block for variant valid scalars. Given a Component_List node
408 -- CL, it generates an 'if' followed by a 'case' statement that compares
409 -- all components of local temporaries named X and Y (that are declared
410 -- as formals at some upper level). E provides the Sloc to be used for
411 -- the generated code.
415 L
: List_Id
) return Node_Id
;
416 -- Building block for variant validate scalars. Given the list, L, of
417 -- components (or discriminants) L, it generates a return statement that
418 -- compares all components of local temporaries named X and Y (that are
419 -- declared as formals at some upper level). E provides the Sloc to be
420 -- used for the generated code.
426 -- <Make_VS_If on shared components>
429 -- when V1 => <Make_VS_Case> on subcomponents
431 -- when Vn => <Make_VS_Case> on subcomponents
434 function Make_VS_Case
437 Discrs
: Elist_Id
:= New_Elmt_List
) return List_Id
439 Loc
: constant Source_Ptr
:= Sloc
(E
);
440 Result
: constant List_Id
:= New_List
;
445 Append_To
(Result
, Make_VS_If
(E
, Component_Items
(CL
)));
447 if No
(Variant_Part
(CL
)) then
451 Variant
:= First_Non_Pragma
(Variants
(Variant_Part
(CL
)));
457 Alt_List
:= New_List
;
458 while Present
(Variant
) loop
460 Make_Case_Statement_Alternative
(Loc
,
461 Discrete_Choices
=> New_Copy_List
(Discrete_Choices
(Variant
)),
463 Make_VS_Case
(E
, Component_List
(Variant
), Discrs
)));
464 Next_Non_Pragma
(Variant
);
468 Make_Case_Statement
(Loc
,
470 Make_Selected_Component
(Loc
,
471 Prefix
=> Make_Identifier
(Loc
, Name_X
),
472 Selector_Name
=> New_Copy
(Name
(Variant_Part
(CL
)))),
473 Alternatives
=> Alt_List
));
485 -- not X.C1'Valid_Scalars
487 -- not X.C2'Valid_Scalars
493 -- or a null statement if the list L is empty
497 L
: List_Id
) return Node_Id
499 Loc
: constant Source_Ptr
:= Sloc
(E
);
502 Field_Name
: Name_Id
;
507 return Make_Null_Statement
(Loc
);
512 C
:= First_Non_Pragma
(L
);
513 while Present
(C
) loop
514 Def_Id
:= Defining_Identifier
(C
);
515 Field_Name
:= Chars
(Def_Id
);
517 -- The tags need not be checked since they will always be valid
519 -- Note also that in the following, we use Make_Identifier for
520 -- the component names. Use of New_Occurrence_Of to identify
521 -- the components would be incorrect because wrong entities for
522 -- discriminants could be picked up in the private type case.
524 -- Don't bother with abstract parent in interface case
526 if Field_Name
= Name_uParent
527 and then Is_Interface
(Etype
(Def_Id
))
531 -- Don't bother with tag, always valid, and not scalar anyway
533 elsif Field_Name
= Name_uTag
then
536 -- Don't bother with component with no scalar components
538 elsif not Scalar_Part_Present
(Etype
(Def_Id
)) then
541 -- Normal case, generate Valid_Scalars attribute reference
544 Evolve_Or_Else
(Cond
,
547 Make_Attribute_Reference
(Loc
,
549 Make_Selected_Component
(Loc
,
551 Make_Identifier
(Loc
, Name_X
),
553 Make_Identifier
(Loc
, Field_Name
)),
554 Attribute_Name
=> Name_Valid_Scalars
)));
561 return Make_Null_Statement
(Loc
);
565 Make_Implicit_If_Statement
(E
,
567 Then_Statements
=> New_List
(
568 Make_Simple_Return_Statement
(Loc
,
570 New_Occurrence_Of
(Standard_False
, Loc
))));
575 -- Local Declarations
577 Def
: constant Node_Id
:= Parent
(R_Type
);
578 Comps
: constant Node_Id
:= Component_List
(Type_Definition
(Def
));
579 Stmts
: constant List_Id
:= New_List
;
580 Pspecs
: constant List_Id
:= New_List
;
584 Make_Parameter_Specification
(Loc
,
585 Defining_Identifier
=> X
,
586 Parameter_Type
=> New_Occurrence_Of
(R_Type
, Loc
)));
589 Make_VS_If
(R_Type
, Discriminant_Specifications
(Def
)));
590 Append_List_To
(Stmts
, Make_VS_Case
(R_Type
, Comps
));
593 Make_Simple_Return_Statement
(Loc
,
594 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
597 Make_Subprogram_Body
(Loc
,
599 Make_Function_Specification
(Loc
,
600 Defining_Unit_Name
=> Func_Id
,
601 Parameter_Specifications
=> Pspecs
,
602 Result_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
)),
603 Declarations
=> New_List
,
604 Handled_Statement_Sequence
=>
605 Make_Handled_Sequence_Of_Statements
(Loc
, Statements
=> Stmts
)),
606 Suppress
=> Discriminant_Check
);
608 if not Debug_Generated_Code
then
609 Set_Debug_Info_Off
(Func_Id
);
612 Set_Is_Pure
(Func_Id
);
614 end Build_Record_VS_Func
;
616 ----------------------------------
617 -- Compile_Stream_Body_In_Scope --
618 ----------------------------------
620 procedure Compile_Stream_Body_In_Scope
626 Installed
: Boolean := False;
627 Scop
: constant Entity_Id
:= Scope
(Arr
);
628 Curr
: constant Entity_Id
:= Current_Scope
;
632 and then not In_Open_Scopes
(Scop
)
633 and then Ekind
(Scop
) = E_Package
635 -- If we are within an instance body, then all visibility has been
636 -- established already and there is no need to install the package.
638 and then not In_Instance_Body
641 Install_Visible_Declarations
(Scop
);
642 Install_Private_Declarations
(Scop
);
645 -- The entities in the package are now visible, but the generated
646 -- stream entity must appear in the current scope (usually an
647 -- enclosing stream function) so that itypes all have their proper
654 Insert_Action
(N
, Decl
);
656 Insert_Action
(N
, Decl
, Suppress
=> All_Checks
);
661 -- Remove extra copy of current scope, and package itself
664 End_Package_Scope
(Scop
);
666 end Compile_Stream_Body_In_Scope
;
668 -----------------------------------
669 -- Expand_Access_To_Protected_Op --
670 -----------------------------------
672 procedure Expand_Access_To_Protected_Op
677 -- The value of the attribute_reference is a record containing two
678 -- fields: an access to the protected object, and an access to the
679 -- subprogram itself. The prefix is a selected component.
681 Loc
: constant Source_Ptr
:= Sloc
(N
);
683 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
686 E_T
: constant Entity_Id
:= Equivalent_Type
(Btyp
);
687 Acc
: constant Entity_Id
:=
688 Etype
(Next_Component
(First_Component
(E_T
)));
692 function May_Be_External_Call
return Boolean;
693 -- If the 'Access is to a local operation, but appears in a context
694 -- where it may lead to a call from outside the object, we must treat
695 -- this as an external call. Clearly we cannot tell without full
696 -- flow analysis, and a subsequent call that uses this 'Access may
697 -- lead to a bounded error (trying to seize locks twice, e.g.). For
698 -- now we treat 'Access as a potential external call if it is an actual
699 -- in a call to an outside subprogram.
701 --------------------------
702 -- May_Be_External_Call --
703 --------------------------
705 function May_Be_External_Call
return Boolean is
707 Par
: Node_Id
:= Parent
(N
);
710 -- Account for the case where the Access attribute is part of a
711 -- named parameter association.
713 if Nkind
(Par
) = N_Parameter_Association
then
717 if Nkind
(Par
) in N_Subprogram_Call
718 and then Is_Entity_Name
(Name
(Par
))
720 Subp
:= Entity
(Name
(Par
));
721 return not In_Open_Scopes
(Scope
(Subp
));
725 end May_Be_External_Call
;
727 -- Start of processing for Expand_Access_To_Protected_Op
730 -- Within the body of the protected type, the prefix designates a local
731 -- operation, and the object is the first parameter of the corresponding
732 -- protected body of the current enclosing operation.
734 if Is_Entity_Name
(Pref
) then
735 if May_Be_External_Call
then
737 New_Occurrence_Of
(External_Subprogram
(Entity
(Pref
)), Loc
);
741 (Protected_Body_Subprogram
(Entity
(Pref
)), Loc
);
744 -- Don't traverse the scopes when the attribute occurs within an init
745 -- proc, because we directly use the _init formal of the init proc in
748 Curr
:= Current_Scope
;
749 if not Is_Init_Proc
(Curr
) then
750 pragma Assert
(In_Open_Scopes
(Scope
(Entity
(Pref
))));
752 while Scope
(Curr
) /= Scope
(Entity
(Pref
)) loop
753 Curr
:= Scope
(Curr
);
757 -- In case of protected entries the first formal of its Protected_
758 -- Body_Subprogram is the address of the object.
760 if Ekind
(Curr
) = E_Entry
then
764 (Protected_Body_Subprogram
(Curr
)), Loc
);
766 -- If the current scope is an init proc, then use the address of the
767 -- _init formal as the object reference.
769 elsif Is_Init_Proc
(Curr
) then
771 Make_Attribute_Reference
(Loc
,
772 Prefix
=> New_Occurrence_Of
(First_Formal
(Curr
), Loc
),
773 Attribute_Name
=> Name_Address
);
775 -- In case of protected subprograms the first formal of its
776 -- Protected_Body_Subprogram is the object and we get its address.
780 Make_Attribute_Reference
(Loc
,
784 (Protected_Body_Subprogram
(Curr
)), Loc
),
785 Attribute_Name
=> Name_Address
);
788 -- Case where the prefix is not an entity name. Find the
789 -- version of the protected operation to be called from
790 -- outside the protected object.
796 (Entity
(Selector_Name
(Pref
))), Loc
);
799 Make_Attribute_Reference
(Loc
,
800 Prefix
=> Relocate_Node
(Prefix
(Pref
)),
801 Attribute_Name
=> Name_Address
);
805 Make_Attribute_Reference
(Loc
,
807 Attribute_Name
=> Name_Access
);
809 -- We set the type of the access reference to the already generated
810 -- access_to_subprogram type, and declare the reference analyzed, to
811 -- prevent further expansion when the enclosing aggregate is analyzed.
813 Set_Etype
(Sub_Ref
, Acc
);
814 Set_Analyzed
(Sub_Ref
);
818 Expressions
=> New_List
(Obj_Ref
, Sub_Ref
));
820 -- Sub_Ref has been marked as analyzed, but we still need to make sure
821 -- Sub is correctly frozen.
823 Freeze_Before
(N
, Entity
(Sub
));
826 Analyze_And_Resolve
(N
, E_T
);
828 -- For subsequent analysis, the node must retain its type. The backend
829 -- will replace it with the equivalent type where needed.
832 end Expand_Access_To_Protected_Op
;
834 --------------------------
835 -- Expand_Fpt_Attribute --
836 --------------------------
838 procedure Expand_Fpt_Attribute
844 Loc
: constant Source_Ptr
:= Sloc
(N
);
845 Typ
: constant Entity_Id
:= Etype
(N
);
849 -- The function name is the selected component Attr_xxx.yyy where
850 -- Attr_xxx is the package name, and yyy is the argument Nam.
852 -- Note: it would be more usual to have separate RE entries for each
853 -- of the entities in the Fat packages, but first they have identical
854 -- names (so we would have to have lots of renaming declarations to
855 -- meet the normal RE rule of separate names for all runtime entities),
856 -- and second there would be an awful lot of them.
859 Make_Selected_Component
(Loc
,
860 Prefix
=> New_Occurrence_Of
(RTE
(Pkg
), Loc
),
861 Selector_Name
=> Make_Identifier
(Loc
, Nam
));
863 -- The generated call is given the provided set of parameters, and then
864 -- wrapped in a conversion which converts the result to the target type
865 -- We use the base type as the target because a range check may be
869 Unchecked_Convert_To
(Base_Type
(Etype
(N
)),
870 Make_Function_Call
(Loc
,
872 Parameter_Associations
=> Args
)));
874 Analyze_And_Resolve
(N
, Typ
);
875 end Expand_Fpt_Attribute
;
877 ----------------------------
878 -- Expand_Fpt_Attribute_R --
879 ----------------------------
881 -- The single argument is converted to its root type to call the
882 -- appropriate runtime function, with the actual call being built
883 -- by Expand_Fpt_Attribute
885 procedure Expand_Fpt_Attribute_R
(N
: Node_Id
) is
886 E1
: constant Node_Id
:= First
(Expressions
(N
));
890 Find_Fat_Info
(Etype
(E1
), Ftp
, Pkg
);
892 (N
, Pkg
, Attribute_Name
(N
),
893 New_List
(Unchecked_Convert_To
(Ftp
, Relocate_Node
(E1
))));
894 end Expand_Fpt_Attribute_R
;
896 -----------------------------
897 -- Expand_Fpt_Attribute_RI --
898 -----------------------------
900 -- The first argument is converted to its root type and the second
901 -- argument is converted to standard long long integer to call the
902 -- appropriate runtime function, with the actual call being built
903 -- by Expand_Fpt_Attribute
905 procedure Expand_Fpt_Attribute_RI
(N
: Node_Id
) is
906 E1
: constant Node_Id
:= First
(Expressions
(N
));
909 E2
: constant Node_Id
:= Next
(E1
);
911 Find_Fat_Info
(Etype
(E1
), Ftp
, Pkg
);
913 (N
, Pkg
, Attribute_Name
(N
),
915 Unchecked_Convert_To
(Ftp
, Relocate_Node
(E1
)),
916 Unchecked_Convert_To
(Standard_Integer
, Relocate_Node
(E2
))));
917 end Expand_Fpt_Attribute_RI
;
919 -----------------------------
920 -- Expand_Fpt_Attribute_RR --
921 -----------------------------
923 -- The two arguments are converted to their root types to call the
924 -- appropriate runtime function, with the actual call being built
925 -- by Expand_Fpt_Attribute
927 procedure Expand_Fpt_Attribute_RR
(N
: Node_Id
) is
928 E1
: constant Node_Id
:= First
(Expressions
(N
));
929 E2
: constant Node_Id
:= Next
(E1
);
934 Find_Fat_Info
(Etype
(E1
), Ftp
, Pkg
);
936 (N
, Pkg
, Attribute_Name
(N
),
938 Unchecked_Convert_To
(Ftp
, Relocate_Node
(E1
)),
939 Unchecked_Convert_To
(Ftp
, Relocate_Node
(E2
))));
940 end Expand_Fpt_Attribute_RR
;
942 ---------------------------------
943 -- Expand_Loop_Entry_Attribute --
944 ---------------------------------
946 procedure Expand_Loop_Entry_Attribute
(N
: Node_Id
) is
947 procedure Build_Conditional_Block
951 If_Stmt
: out Node_Id
;
952 Blk_Stmt
: out Node_Id
);
953 -- Create a block Blk_Stmt with an empty declarative list and a single
954 -- loop Loop_Stmt. The block is encased in an if statement If_Stmt with
955 -- condition Cond. If_Stmt is Empty when there is no condition provided.
957 function Is_Array_Iteration
(N
: Node_Id
) return Boolean;
958 -- Determine whether loop statement N denotes an Ada 2012 iteration over
961 -----------------------------
962 -- Build_Conditional_Block --
963 -----------------------------
965 procedure Build_Conditional_Block
969 If_Stmt
: out Node_Id
;
970 Blk_Stmt
: out Node_Id
)
973 -- Do not reanalyze the original loop statement because it is simply
976 Set_Analyzed
(Loop_Stmt
);
979 Make_Block_Statement
(Loc
,
980 Declarations
=> New_List
,
981 Handled_Statement_Sequence
=>
982 Make_Handled_Sequence_Of_Statements
(Loc
,
983 Statements
=> New_List
(Loop_Stmt
)));
985 if Present
(Cond
) then
987 Make_If_Statement
(Loc
,
989 Then_Statements
=> New_List
(Blk_Stmt
));
993 end Build_Conditional_Block
;
995 ------------------------
996 -- Is_Array_Iteration --
997 ------------------------
999 function Is_Array_Iteration
(N
: Node_Id
) return Boolean is
1000 Stmt
: constant Node_Id
:= Original_Node
(N
);
1004 if Nkind
(Stmt
) = N_Loop_Statement
1005 and then Present
(Iteration_Scheme
(Stmt
))
1006 and then Present
(Iterator_Specification
(Iteration_Scheme
(Stmt
)))
1008 Iter
:= Iterator_Specification
(Iteration_Scheme
(Stmt
));
1011 Of_Present
(Iter
) and then Is_Array_Type
(Etype
(Name
(Iter
)));
1015 end Is_Array_Iteration
;
1019 Exprs
: constant List_Id
:= Expressions
(N
);
1020 Pref
: constant Node_Id
:= Prefix
(N
);
1021 Typ
: constant Entity_Id
:= Etype
(Pref
);
1024 Installed
: Boolean;
1026 Loop_Id
: Entity_Id
;
1027 Loop_Stmt
: Node_Id
;
1030 Temp_Decl
: Node_Id
;
1031 Temp_Id
: Entity_Id
;
1033 -- Start of processing for Expand_Loop_Entry_Attribute
1036 -- Step 1: Find the related loop
1038 -- The loop label variant of attribute 'Loop_Entry already has all the
1039 -- information in its expression.
1041 if Present
(Exprs
) then
1042 Loop_Id
:= Entity
(First
(Exprs
));
1043 Loop_Stmt
:= Label_Construct
(Parent
(Loop_Id
));
1045 -- Climb the parent chain to find the nearest enclosing loop. Skip all
1046 -- internally generated loops for quantified expressions.
1050 while Present
(Loop_Stmt
) loop
1051 if Nkind
(Loop_Stmt
) = N_Loop_Statement
1052 and then Present
(Identifier
(Loop_Stmt
))
1057 Loop_Stmt
:= Parent
(Loop_Stmt
);
1060 Loop_Id
:= Entity
(Identifier
(Loop_Stmt
));
1063 Loc
:= Sloc
(Loop_Stmt
);
1065 -- Step 2: Transform the loop
1067 -- The loop has already been transformed during the expansion of a prior
1068 -- 'Loop_Entry attribute. Retrieve the declarative list of the block.
1070 if Has_Loop_Entry_Attributes
(Loop_Id
) then
1072 -- When the related loop name appears as the argument of attribute
1073 -- Loop_Entry, the corresponding label construct is the generated
1074 -- block statement. This is because the expander reuses the label.
1076 if Nkind
(Loop_Stmt
) = N_Block_Statement
then
1077 Decls
:= Declarations
(Loop_Stmt
);
1079 -- In all other cases, the loop must appear in the handled sequence
1080 -- of statements of the generated block.
1084 (Nkind
(Parent
(Loop_Stmt
)) = N_Handled_Sequence_Of_Statements
1086 Nkind
(Parent
(Parent
(Loop_Stmt
))) = N_Block_Statement
);
1088 Decls
:= Declarations
(Parent
(Parent
(Loop_Stmt
)));
1093 -- Transform the loop into a conditional block
1096 Set_Has_Loop_Entry_Attributes
(Loop_Id
);
1097 Scheme
:= Iteration_Scheme
(Loop_Stmt
);
1099 -- Infinite loops are transformed into:
1102 -- Temp1 : constant <type of Pref1> := <Pref1>;
1104 -- TempN : constant <type of PrefN> := <PrefN>;
1107 -- <original source statements with attribute rewrites>
1112 Build_Conditional_Block
(Loc
,
1114 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1120 -- While loops are transformed into:
1122 -- function Fnn return Boolean is
1124 -- <condition actions>
1125 -- return <condition>;
1130 -- Temp1 : constant <type of Pref1> := <Pref1>;
1132 -- TempN : constant <type of PrefN> := <PrefN>;
1135 -- <original source statements with attribute rewrites>
1136 -- exit when not Fnn;
1141 -- Note that loops over iterators and containers are already
1142 -- converted into while loops.
1144 elsif Present
(Condition
(Scheme
)) then
1146 Func_Decl
: Node_Id
;
1147 Func_Id
: Entity_Id
;
1151 -- Wrap the condition of the while loop in a Boolean function.
1152 -- This avoids the duplication of the same code which may lead
1153 -- to gigi issues with respect to multiple declaration of the
1154 -- same entity in the presence of side effects or checks. Note
1155 -- that the condition actions must also be relocated to the
1156 -- wrapping function.
1159 -- <condition actions>
1160 -- return <condition>;
1162 if Present
(Condition_Actions
(Scheme
)) then
1163 Stmts
:= Condition_Actions
(Scheme
);
1169 Make_Simple_Return_Statement
(Loc
,
1170 Expression
=> Relocate_Node
(Condition
(Scheme
))));
1173 -- function Fnn return Boolean is
1178 Func_Id
:= Make_Temporary
(Loc
, 'F');
1180 Make_Subprogram_Body
(Loc
,
1182 Make_Function_Specification
(Loc
,
1183 Defining_Unit_Name
=> Func_Id
,
1184 Result_Definition
=>
1185 New_Occurrence_Of
(Standard_Boolean
, Loc
)),
1186 Declarations
=> Empty_List
,
1187 Handled_Statement_Sequence
=>
1188 Make_Handled_Sequence_Of_Statements
(Loc
,
1189 Statements
=> Stmts
));
1191 -- The function is inserted before the related loop. Make sure
1192 -- to analyze it in the context of the loop's enclosing scope.
1194 Push_Scope
(Scope
(Loop_Id
));
1195 Insert_Action
(Loop_Stmt
, Func_Decl
);
1198 -- Transform the original while loop into an infinite loop
1199 -- where the last statement checks the negated condition. This
1200 -- placement ensures that the condition will not be evaluated
1201 -- twice on the first iteration.
1203 Set_Iteration_Scheme
(Loop_Stmt
, Empty
);
1207 -- exit when not Fnn;
1209 Append_To
(Statements
(Loop_Stmt
),
1210 Make_Exit_Statement
(Loc
,
1214 Make_Function_Call
(Loc
,
1215 Name
=> New_Occurrence_Of
(Func_Id
, Loc
)))));
1217 Build_Conditional_Block
(Loc
,
1219 Make_Function_Call
(Loc
,
1220 Name
=> New_Occurrence_Of
(Func_Id
, Loc
)),
1221 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1226 -- Ada 2012 iteration over an array is transformed into:
1228 -- if <Array_Nam>'Length (1) > 0
1229 -- and then <Array_Nam>'Length (N) > 0
1232 -- Temp1 : constant <type of Pref1> := <Pref1>;
1234 -- TempN : constant <type of PrefN> := <PrefN>;
1236 -- for X in ... loop -- multiple loops depending on dims
1237 -- <original source statements with attribute rewrites>
1242 elsif Is_Array_Iteration
(Loop_Stmt
) then
1244 Array_Nam
: constant Entity_Id
:=
1245 Entity
(Name
(Iterator_Specification
1246 (Iteration_Scheme
(Original_Node
(Loop_Stmt
)))));
1247 Num_Dims
: constant Pos
:=
1248 Number_Dimensions
(Etype
(Array_Nam
));
1249 Cond
: Node_Id
:= Empty
;
1253 -- Generate a check which determines whether all dimensions of
1254 -- the array are non-null.
1256 for Dim
in 1 .. Num_Dims
loop
1260 Make_Attribute_Reference
(Loc
,
1261 Prefix
=> New_Occurrence_Of
(Array_Nam
, Loc
),
1262 Attribute_Name
=> Name_Length
,
1263 Expressions
=> New_List
(
1264 Make_Integer_Literal
(Loc
, Dim
))),
1266 Make_Integer_Literal
(Loc
, 0));
1274 Right_Opnd
=> Check
);
1278 Build_Conditional_Block
(Loc
,
1280 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1285 -- For loops are transformed into:
1287 -- if <Low> <= <High> then
1289 -- Temp1 : constant <type of Pref1> := <Pref1>;
1291 -- TempN : constant <type of PrefN> := <PrefN>;
1293 -- for <Def_Id> in <Low> .. <High> loop
1294 -- <original source statements with attribute rewrites>
1299 elsif Present
(Loop_Parameter_Specification
(Scheme
)) then
1301 Loop_Spec
: constant Node_Id
:=
1302 Loop_Parameter_Specification
(Scheme
);
1307 Subt_Def
:= Discrete_Subtype_Definition
(Loop_Spec
);
1309 -- When the loop iterates over a subtype indication with a
1310 -- range, use the low and high bounds of the subtype itself.
1312 if Nkind
(Subt_Def
) = N_Subtype_Indication
then
1313 Subt_Def
:= Scalar_Range
(Etype
(Subt_Def
));
1316 pragma Assert
(Nkind
(Subt_Def
) = N_Range
);
1323 Left_Opnd
=> New_Copy_Tree
(Low_Bound
(Subt_Def
)),
1324 Right_Opnd
=> New_Copy_Tree
(High_Bound
(Subt_Def
)));
1326 Build_Conditional_Block
(Loc
,
1328 Loop_Stmt
=> Relocate_Node
(Loop_Stmt
),
1334 Decls
:= Declarations
(Blk
);
1337 -- Step 3: Create a constant to capture the value of the prefix at the
1338 -- entry point into the loop.
1341 -- Temp : constant <type of Pref> := <Pref>;
1343 Temp_Id
:= Make_Temporary
(Loc
, 'P');
1346 Make_Object_Declaration
(Loc
,
1347 Defining_Identifier
=> Temp_Id
,
1348 Constant_Present
=> True,
1349 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
1350 Expression
=> Relocate_Node
(Pref
));
1351 Append_To
(Decls
, Temp_Decl
);
1353 -- Step 4: Analyze all bits
1355 Installed
:= Current_Scope
= Scope
(Loop_Id
);
1357 -- Depending on the pracement of attribute 'Loop_Entry relative to the
1358 -- associated loop, ensure the proper visibility for analysis.
1360 if not Installed
then
1361 Push_Scope
(Scope
(Loop_Id
));
1364 -- The analysis of the conditional block takes care of the constant
1367 if Present
(Result
) then
1368 Rewrite
(Loop_Stmt
, Result
);
1369 Analyze
(Loop_Stmt
);
1371 -- The conditional block was analyzed when a previous 'Loop_Entry was
1372 -- expanded. There is no point in reanalyzing the block, simply analyze
1373 -- the declaration of the constant.
1376 Analyze
(Temp_Decl
);
1379 Rewrite
(N
, New_Occurrence_Of
(Temp_Id
, Loc
));
1382 if not Installed
then
1385 end Expand_Loop_Entry_Attribute
;
1387 ------------------------------
1388 -- Expand_Min_Max_Attribute --
1389 ------------------------------
1391 procedure Expand_Min_Max_Attribute
(N
: Node_Id
) is
1393 -- Min and Max are handled by the back end (except that static cases
1394 -- have already been evaluated during semantic processing, although the
1395 -- back end should not count on this). The one bit of special processing
1396 -- required in the normal case is that these two attributes typically
1397 -- generate conditionals in the code, so check the relevant restriction.
1399 Check_Restriction
(No_Implicit_Conditionals
, N
);
1401 -- In Modify_Tree_For_C mode, we rewrite as an if expression
1403 if Modify_Tree_For_C
then
1405 Loc
: constant Source_Ptr
:= Sloc
(N
);
1406 Typ
: constant Entity_Id
:= Etype
(N
);
1407 Expr
: constant Node_Id
:= First
(Expressions
(N
));
1408 Left
: constant Node_Id
:= Relocate_Node
(Expr
);
1409 Right
: constant Node_Id
:= Relocate_Node
(Next
(Expr
));
1411 function Make_Compare
(Left
, Right
: Node_Id
) return Node_Id
;
1412 -- Returns Left >= Right for Max, Left <= Right for Min
1418 function Make_Compare
(Left
, Right
: Node_Id
) return Node_Id
is
1420 if Attribute_Name
(N
) = Name_Max
then
1424 Right_Opnd
=> Right
);
1429 Right_Opnd
=> Right
);
1433 -- Start of processing for Min_Max
1436 -- If both Left and Right are side effect free, then we can just
1437 -- use Duplicate_Expr to duplicate the references and return
1439 -- (if Left >=|<= Right then Left else Right)
1441 if Side_Effect_Free
(Left
) and then Side_Effect_Free
(Right
) then
1443 Make_If_Expression
(Loc
,
1444 Expressions
=> New_List
(
1445 Make_Compare
(Left
, Right
),
1446 Duplicate_Subexpr_No_Checks
(Left
),
1447 Duplicate_Subexpr_No_Checks
(Right
))));
1449 -- Otherwise we generate declarations to capture the values. We
1450 -- can't put these declarations inside the if expression, since
1451 -- we could end up with an N_Expression_With_Actions which has
1452 -- declarations in the actions, forbidden for Modify_Tree_For_C.
1454 -- The translation is
1456 -- T1 : styp; -- inserted high up in tree
1457 -- T2 : styp; -- inserted high up in tree
1460 -- T1 := styp!(Left);
1461 -- T2 := styp!(Right);
1463 -- (if T1 >=|<= T2 then typ!(T1) else typ!(T2))
1466 -- We insert the T1,T2 declarations with Insert_Declaration which
1467 -- inserts these declarations high up in the tree unconditionally.
1468 -- This is safe since no code is associated with the declarations.
1469 -- Here styp is a standard type whose Esize matches the size of
1470 -- our type. We do this because the actual type may be a result of
1471 -- some local declaration which would not be visible at the point
1472 -- where we insert the declarations of T1 and T2.
1476 T1
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', Left
);
1477 T2
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', Left
);
1478 Styp
: constant Entity_Id
:= Matching_Standard_Type
(Typ
);
1481 Insert_Declaration
(N
,
1482 Make_Object_Declaration
(Loc
,
1483 Defining_Identifier
=> T1
,
1484 Object_Definition
=> New_Occurrence_Of
(Styp
, Loc
)));
1486 Insert_Declaration
(N
,
1487 Make_Object_Declaration
(Loc
,
1488 Defining_Identifier
=> T2
,
1489 Object_Definition
=> New_Occurrence_Of
(Styp
, Loc
)));
1492 Make_Expression_With_Actions
(Loc
,
1493 Actions
=> New_List
(
1494 Make_Assignment_Statement
(Loc
,
1495 Name
=> New_Occurrence_Of
(T1
, Loc
),
1496 Expression
=> Unchecked_Convert_To
(Styp
, Left
)),
1497 Make_Assignment_Statement
(Loc
,
1498 Name
=> New_Occurrence_Of
(T2
, Loc
),
1499 Expression
=> Unchecked_Convert_To
(Styp
, Right
))),
1502 Make_If_Expression
(Loc
,
1503 Expressions
=> New_List
(
1505 (New_Occurrence_Of
(T1
, Loc
),
1506 New_Occurrence_Of
(T2
, Loc
)),
1507 Unchecked_Convert_To
(Typ
,
1508 New_Occurrence_Of
(T1
, Loc
)),
1509 Unchecked_Convert_To
(Typ
,
1510 New_Occurrence_Of
(T2
, Loc
))))));
1514 Analyze_And_Resolve
(N
, Typ
);
1517 end Expand_Min_Max_Attribute
;
1519 ----------------------------------
1520 -- Expand_N_Attribute_Reference --
1521 ----------------------------------
1523 procedure Expand_N_Attribute_Reference
(N
: Node_Id
) is
1524 Loc
: constant Source_Ptr
:= Sloc
(N
);
1525 Typ
: constant Entity_Id
:= Etype
(N
);
1526 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
1527 Pref
: constant Node_Id
:= Prefix
(N
);
1528 Ptyp
: constant Entity_Id
:= Etype
(Pref
);
1529 Exprs
: constant List_Id
:= Expressions
(N
);
1530 Id
: constant Attribute_Id
:= Get_Attribute_Id
(Attribute_Name
(N
));
1532 procedure Rewrite_Stream_Proc_Call
(Pname
: Entity_Id
);
1533 -- Rewrites a stream attribute for Read, Write or Output with the
1534 -- procedure call. Pname is the entity for the procedure to call.
1536 ------------------------------
1537 -- Rewrite_Stream_Proc_Call --
1538 ------------------------------
1540 procedure Rewrite_Stream_Proc_Call
(Pname
: Entity_Id
) is
1541 Item
: constant Node_Id
:= Next
(First
(Exprs
));
1542 Formal
: constant Entity_Id
:= Next_Formal
(First_Formal
(Pname
));
1543 Formal_Typ
: constant Entity_Id
:= Etype
(Formal
);
1544 Is_Written
: constant Boolean := (Ekind
(Formal
) /= E_In_Parameter
);
1547 -- The expansion depends on Item, the second actual, which is
1548 -- the object being streamed in or out.
1550 -- If the item is a component of a packed array type, and
1551 -- a conversion is needed on exit, we introduce a temporary to
1552 -- hold the value, because otherwise the packed reference will
1553 -- not be properly expanded.
1555 if Nkind
(Item
) = N_Indexed_Component
1556 and then Is_Packed
(Base_Type
(Etype
(Prefix
(Item
))))
1557 and then Base_Type
(Etype
(Item
)) /= Base_Type
(Formal_Typ
)
1561 Temp
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
1567 Make_Object_Declaration
(Loc
,
1568 Defining_Identifier
=> Temp
,
1569 Object_Definition
=>
1570 New_Occurrence_Of
(Formal_Typ
, Loc
));
1571 Set_Etype
(Temp
, Formal_Typ
);
1574 Make_Assignment_Statement
(Loc
,
1575 Name
=> New_Copy_Tree
(Item
),
1577 Unchecked_Convert_To
1578 (Etype
(Item
), New_Occurrence_Of
(Temp
, Loc
)));
1580 Rewrite
(Item
, New_Occurrence_Of
(Temp
, Loc
));
1584 Make_Procedure_Call_Statement
(Loc
,
1585 Name
=> New_Occurrence_Of
(Pname
, Loc
),
1586 Parameter_Associations
=> Exprs
),
1589 Rewrite
(N
, Make_Null_Statement
(Loc
));
1594 -- For the class-wide dispatching cases, and for cases in which
1595 -- the base type of the second argument matches the base type of
1596 -- the corresponding formal parameter (that is to say the stream
1597 -- operation is not inherited), we are all set, and can use the
1598 -- argument unchanged.
1600 -- For all other cases we do an unchecked conversion of the second
1601 -- parameter to the type of the formal of the procedure we are
1602 -- calling. This deals with the private type cases, and with going
1603 -- to the root type as required in elementary type case.
1605 if not Is_Class_Wide_Type
(Entity
(Pref
))
1606 and then not Is_Class_Wide_Type
(Etype
(Item
))
1607 and then Base_Type
(Etype
(Item
)) /= Base_Type
(Formal_Typ
)
1610 Unchecked_Convert_To
(Formal_Typ
, Relocate_Node
(Item
)));
1612 -- For untagged derived types set Assignment_OK, to prevent
1613 -- copies from being created when the unchecked conversion
1614 -- is expanded (which would happen in Remove_Side_Effects
1615 -- if Expand_N_Unchecked_Conversion were allowed to call
1616 -- Force_Evaluation). The copy could violate Ada semantics in
1617 -- cases such as an actual that is an out parameter. Note that
1618 -- this approach is also used in exp_ch7 for calls to controlled
1619 -- type operations to prevent problems with actuals wrapped in
1620 -- unchecked conversions.
1622 if Is_Untagged_Derivation
(Etype
(Expression
(Item
))) then
1623 Set_Assignment_OK
(Item
);
1627 -- The stream operation to call may be a renaming created by an
1628 -- attribute definition clause, and may not be frozen yet. Ensure
1629 -- that it has the necessary extra formals.
1631 if not Is_Frozen
(Pname
) then
1632 Create_Extra_Formals
(Pname
);
1635 -- And now rewrite the call
1638 Make_Procedure_Call_Statement
(Loc
,
1639 Name
=> New_Occurrence_Of
(Pname
, Loc
),
1640 Parameter_Associations
=> Exprs
));
1643 end Rewrite_Stream_Proc_Call
;
1645 -- Start of processing for Expand_N_Attribute_Reference
1648 -- Do required validity checking, if enabled. Do not apply check to
1649 -- output parameters of an Asm instruction, since the value of this
1650 -- is not set till after the attribute has been elaborated, and do
1651 -- not apply the check to the arguments of a 'Read or 'Input attribute
1652 -- reference since the scalar argument is an OUT scalar.
1654 if Validity_Checks_On
and then Validity_Check_Operands
1655 and then Id
/= Attribute_Asm_Output
1656 and then Id
/= Attribute_Read
1657 and then Id
/= Attribute_Input
1662 Expr
:= First
(Expressions
(N
));
1663 while Present
(Expr
) loop
1664 Ensure_Valid
(Expr
);
1670 -- Ada 2005 (AI-318-02): If attribute prefix is a call to a build-in-
1671 -- place function, then a temporary return object needs to be created
1672 -- and access to it must be passed to the function. Currently we limit
1673 -- such functions to those with inherently limited result subtypes, but
1674 -- eventually we plan to expand the functions that are treated as
1675 -- build-in-place to include other composite result types.
1677 if Ada_Version
>= Ada_2005
1678 and then Is_Build_In_Place_Function_Call
(Pref
)
1680 Make_Build_In_Place_Call_In_Anonymous_Context
(Pref
);
1683 -- If prefix is a protected type name, this is a reference to the
1684 -- current instance of the type. For a component definition, nothing
1685 -- to do (expansion will occur in the init proc). In other contexts,
1686 -- rewrite into reference to current instance.
1688 if Is_Protected_Self_Reference
(Pref
)
1690 (Nkind_In
(Parent
(N
), N_Index_Or_Discriminant_Constraint
,
1691 N_Discriminant_Association
)
1692 and then Nkind
(Parent
(Parent
(Parent
(Parent
(N
))))) =
1693 N_Component_Definition
)
1695 -- No action needed for these attributes since the current instance
1696 -- will be rewritten to be the name of the _object parameter
1697 -- associated with the enclosing protected subprogram (see below).
1699 and then Id
/= Attribute_Access
1700 and then Id
/= Attribute_Unchecked_Access
1701 and then Id
/= Attribute_Unrestricted_Access
1703 Rewrite
(Pref
, Concurrent_Ref
(Pref
));
1707 -- Remaining processing depends on specific attribute
1709 -- Note: individual sections of the following case statement are
1710 -- allowed to assume there is no code after the case statement, and
1711 -- are legitimately allowed to execute return statements if they have
1712 -- nothing more to do.
1716 -- Attributes related to Ada 2012 iterators
1718 when Attribute_Constant_Indexing |
1719 Attribute_Default_Iterator |
1720 Attribute_Implicit_Dereference |
1721 Attribute_Iterable |
1722 Attribute_Iterator_Element |
1723 Attribute_Variable_Indexing
=>
1726 -- Internal attributes used to deal with Ada 2012 delayed aspects. These
1727 -- were already rejected by the parser. Thus they shouldn't appear here.
1729 when Internal_Attribute_Id
=>
1730 raise Program_Error
;
1736 when Attribute_Access |
1737 Attribute_Unchecked_Access |
1738 Attribute_Unrestricted_Access
=>
1740 Access_Cases
: declare
1741 Ref_Object
: constant Node_Id
:= Get_Referenced_Object
(Pref
);
1742 Btyp_DDT
: Entity_Id
;
1744 function Enclosing_Object
(N
: Node_Id
) return Node_Id
;
1745 -- If N denotes a compound name (selected component, indexed
1746 -- component, or slice), returns the name of the outermost such
1747 -- enclosing object. Otherwise returns N. If the object is a
1748 -- renaming, then the renamed object is returned.
1750 ----------------------
1751 -- Enclosing_Object --
1752 ----------------------
1754 function Enclosing_Object
(N
: Node_Id
) return Node_Id
is
1759 while Nkind_In
(Obj_Name
, N_Selected_Component
,
1760 N_Indexed_Component
,
1763 Obj_Name
:= Prefix
(Obj_Name
);
1766 return Get_Referenced_Object
(Obj_Name
);
1767 end Enclosing_Object
;
1769 -- Local declarations
1771 Enc_Object
: constant Node_Id
:= Enclosing_Object
(Ref_Object
);
1773 -- Start of processing for Access_Cases
1776 Btyp_DDT
:= Designated_Type
(Btyp
);
1778 -- Handle designated types that come from the limited view
1780 if Ekind
(Btyp_DDT
) = E_Incomplete_Type
1781 and then From_Limited_With
(Btyp_DDT
)
1782 and then Present
(Non_Limited_View
(Btyp_DDT
))
1784 Btyp_DDT
:= Non_Limited_View
(Btyp_DDT
);
1786 elsif Is_Class_Wide_Type
(Btyp_DDT
)
1787 and then Ekind
(Etype
(Btyp_DDT
)) = E_Incomplete_Type
1788 and then From_Limited_With
(Etype
(Btyp_DDT
))
1789 and then Present
(Non_Limited_View
(Etype
(Btyp_DDT
)))
1790 and then Present
(Class_Wide_Type
1791 (Non_Limited_View
(Etype
(Btyp_DDT
))))
1794 Class_Wide_Type
(Non_Limited_View
(Etype
(Btyp_DDT
)));
1797 -- In order to improve the text of error messages, the designated
1798 -- type of access-to-subprogram itypes is set by the semantics as
1799 -- the associated subprogram entity (see sem_attr). Now we replace
1800 -- such node with the proper E_Subprogram_Type itype.
1802 if Id
= Attribute_Unrestricted_Access
1803 and then Is_Subprogram
(Directly_Designated_Type
(Typ
))
1805 -- The following conditions ensure that this special management
1806 -- is done only for "Address!(Prim'Unrestricted_Access)" nodes.
1807 -- At this stage other cases in which the designated type is
1808 -- still a subprogram (instead of an E_Subprogram_Type) are
1809 -- wrong because the semantics must have overridden the type of
1810 -- the node with the type imposed by the context.
1812 if Nkind
(Parent
(N
)) = N_Unchecked_Type_Conversion
1813 and then Etype
(Parent
(N
)) = RTE
(RE_Prim_Ptr
)
1815 Set_Etype
(N
, RTE
(RE_Prim_Ptr
));
1819 Subp
: constant Entity_Id
:=
1820 Directly_Designated_Type
(Typ
);
1822 Extra
: Entity_Id
:= Empty
;
1823 New_Formal
: Entity_Id
;
1824 Old_Formal
: Entity_Id
:= First_Formal
(Subp
);
1825 Subp_Typ
: Entity_Id
;
1828 Subp_Typ
:= Create_Itype
(E_Subprogram_Type
, N
);
1829 Set_Etype
(Subp_Typ
, Etype
(Subp
));
1830 Set_Returns_By_Ref
(Subp_Typ
, Returns_By_Ref
(Subp
));
1832 if Present
(Old_Formal
) then
1833 New_Formal
:= New_Copy
(Old_Formal
);
1834 Set_First_Entity
(Subp_Typ
, New_Formal
);
1837 Set_Scope
(New_Formal
, Subp_Typ
);
1838 Etyp
:= Etype
(New_Formal
);
1840 -- Handle itypes. There is no need to duplicate
1841 -- here the itypes associated with record types
1842 -- (i.e the implicit full view of private types).
1845 and then Ekind
(Base_Type
(Etyp
)) /= E_Record_Type
1847 Extra
:= New_Copy
(Etyp
);
1848 Set_Parent
(Extra
, New_Formal
);
1849 Set_Etype
(New_Formal
, Extra
);
1850 Set_Scope
(Extra
, Subp_Typ
);
1853 Extra
:= New_Formal
;
1854 Next_Formal
(Old_Formal
);
1855 exit when No
(Old_Formal
);
1857 Set_Next_Entity
(New_Formal
,
1858 New_Copy
(Old_Formal
));
1859 Next_Entity
(New_Formal
);
1862 Set_Next_Entity
(New_Formal
, Empty
);
1863 Set_Last_Entity
(Subp_Typ
, Extra
);
1866 -- Now that the explicit formals have been duplicated,
1867 -- any extra formals needed by the subprogram must be
1870 if Present
(Extra
) then
1871 Set_Extra_Formal
(Extra
, Empty
);
1874 Create_Extra_Formals
(Subp_Typ
);
1875 Set_Directly_Designated_Type
(Typ
, Subp_Typ
);
1880 if Is_Access_Protected_Subprogram_Type
(Btyp
) then
1881 Expand_Access_To_Protected_Op
(N
, Pref
, Typ
);
1883 -- If prefix is a type name, this is a reference to the current
1884 -- instance of the type, within its initialization procedure.
1886 elsif Is_Entity_Name
(Pref
)
1887 and then Is_Type
(Entity
(Pref
))
1894 -- If the current instance name denotes a task type, then
1895 -- the access attribute is rewritten to be the name of the
1896 -- "_task" parameter associated with the task type's task
1897 -- procedure. An unchecked conversion is applied to ensure
1898 -- a type match in cases of expander-generated calls (e.g.
1901 if Is_Task_Type
(Entity
(Pref
)) then
1903 First_Entity
(Get_Task_Body_Procedure
(Entity
(Pref
)));
1904 while Present
(Formal
) loop
1905 exit when Chars
(Formal
) = Name_uTask
;
1906 Next_Entity
(Formal
);
1909 pragma Assert
(Present
(Formal
));
1912 Unchecked_Convert_To
(Typ
,
1913 New_Occurrence_Of
(Formal
, Loc
)));
1916 elsif Is_Protected_Type
(Entity
(Pref
)) then
1918 -- No action needed for current instance located in a
1919 -- component definition (expansion will occur in the
1922 if Is_Protected_Type
(Current_Scope
) then
1925 -- If the current instance reference is located in a
1926 -- protected subprogram or entry then rewrite the access
1927 -- attribute to be the name of the "_object" parameter.
1928 -- An unchecked conversion is applied to ensure a type
1929 -- match in cases of expander-generated calls (e.g. init
1932 -- The code may be nested in a block, so find enclosing
1933 -- scope that is a protected operation.
1940 Subp
:= Current_Scope
;
1941 while Ekind_In
(Subp
, E_Loop
, E_Block
) loop
1942 Subp
:= Scope
(Subp
);
1947 (Protected_Body_Subprogram
(Subp
));
1949 -- For a protected subprogram the _Object parameter
1950 -- is the protected record, so we create an access
1951 -- to it. The _Object parameter of an entry is an
1954 if Ekind
(Subp
) = E_Entry
then
1956 Unchecked_Convert_To
(Typ
,
1957 New_Occurrence_Of
(Formal
, Loc
)));
1962 Unchecked_Convert_To
(Typ
,
1963 Make_Attribute_Reference
(Loc
,
1964 Attribute_Name
=> Name_Unrestricted_Access
,
1966 New_Occurrence_Of
(Formal
, Loc
))));
1967 Analyze_And_Resolve
(N
);
1972 -- The expression must appear in a default expression,
1973 -- (which in the initialization procedure is the right-hand
1974 -- side of an assignment), and not in a discriminant
1979 while Present
(Par
) loop
1980 exit when Nkind
(Par
) = N_Assignment_Statement
;
1982 if Nkind
(Par
) = N_Component_Declaration
then
1986 Par
:= Parent
(Par
);
1989 if Present
(Par
) then
1991 Make_Attribute_Reference
(Loc
,
1992 Prefix
=> Make_Identifier
(Loc
, Name_uInit
),
1993 Attribute_Name
=> Attribute_Name
(N
)));
1995 Analyze_And_Resolve
(N
, Typ
);
2000 -- If the prefix of an Access attribute is a dereference of an
2001 -- access parameter (or a renaming of such a dereference, or a
2002 -- subcomponent of such a dereference) and the context is a
2003 -- general access type (including the type of an object or
2004 -- component with an access_definition, but not the anonymous
2005 -- type of an access parameter or access discriminant), then
2006 -- apply an accessibility check to the access parameter. We used
2007 -- to rewrite the access parameter as a type conversion, but that
2008 -- could only be done if the immediate prefix of the Access
2009 -- attribute was the dereference, and didn't handle cases where
2010 -- the attribute is applied to a subcomponent of the dereference,
2011 -- since there's generally no available, appropriate access type
2012 -- to convert to in that case. The attribute is passed as the
2013 -- point to insert the check, because the access parameter may
2014 -- come from a renaming, possibly in a different scope, and the
2015 -- check must be associated with the attribute itself.
2017 elsif Id
= Attribute_Access
2018 and then Nkind
(Enc_Object
) = N_Explicit_Dereference
2019 and then Is_Entity_Name
(Prefix
(Enc_Object
))
2020 and then (Ekind
(Btyp
) = E_General_Access_Type
2021 or else Is_Local_Anonymous_Access
(Btyp
))
2022 and then Ekind
(Entity
(Prefix
(Enc_Object
))) in Formal_Kind
2023 and then Ekind
(Etype
(Entity
(Prefix
(Enc_Object
))))
2024 = E_Anonymous_Access_Type
2025 and then Present
(Extra_Accessibility
2026 (Entity
(Prefix
(Enc_Object
))))
2028 Apply_Accessibility_Check
(Prefix
(Enc_Object
), Typ
, N
);
2030 -- Ada 2005 (AI-251): If the designated type is an interface we
2031 -- add an implicit conversion to force the displacement of the
2032 -- pointer to reference the secondary dispatch table.
2034 elsif Is_Interface
(Btyp_DDT
)
2035 and then (Comes_From_Source
(N
)
2036 or else Comes_From_Source
(Ref_Object
)
2037 or else (Nkind
(Ref_Object
) in N_Has_Chars
2038 and then Chars
(Ref_Object
) = Name_uInit
))
2040 if Nkind
(Ref_Object
) /= N_Explicit_Dereference
then
2042 -- No implicit conversion required if types match, or if
2043 -- the prefix is the class_wide_type of the interface. In
2044 -- either case passing an object of the interface type has
2045 -- already set the pointer correctly.
2047 if Btyp_DDT
= Etype
(Ref_Object
)
2048 or else (Is_Class_Wide_Type
(Etype
(Ref_Object
))
2050 Class_Wide_Type
(Btyp_DDT
) = Etype
(Ref_Object
))
2055 Rewrite
(Prefix
(N
),
2056 Convert_To
(Btyp_DDT
,
2057 New_Copy_Tree
(Prefix
(N
))));
2059 Analyze_And_Resolve
(Prefix
(N
), Btyp_DDT
);
2062 -- When the object is an explicit dereference, convert the
2063 -- dereference's prefix.
2067 Obj_DDT
: constant Entity_Id
:=
2069 (Directly_Designated_Type
2070 (Etype
(Prefix
(Ref_Object
))));
2072 -- No implicit conversion required if designated types
2073 -- match, or if we have an unrestricted access.
2075 if Obj_DDT
/= Btyp_DDT
2076 and then Id
/= Attribute_Unrestricted_Access
2077 and then not (Is_Class_Wide_Type
(Obj_DDT
)
2078 and then Etype
(Obj_DDT
) = Btyp_DDT
)
2082 New_Copy_Tree
(Prefix
(Ref_Object
))));
2083 Analyze_And_Resolve
(N
, Typ
);
2094 -- Transforms 'Adjacent into a call to the floating-point attribute
2095 -- function Adjacent in Fat_xxx (where xxx is the root type)
2097 when Attribute_Adjacent
=>
2098 Expand_Fpt_Attribute_RR
(N
);
2104 when Attribute_Address
=> Address
: declare
2105 Task_Proc
: Entity_Id
;
2108 -- If the prefix is a task or a task type, the useful address is that
2109 -- of the procedure for the task body, i.e. the actual program unit.
2110 -- We replace the original entity with that of the procedure.
2112 if Is_Entity_Name
(Pref
)
2113 and then Is_Task_Type
(Entity
(Pref
))
2115 Task_Proc
:= Next_Entity
(Root_Type
(Ptyp
));
2117 while Present
(Task_Proc
) loop
2118 exit when Ekind
(Task_Proc
) = E_Procedure
2119 and then Etype
(First_Formal
(Task_Proc
)) =
2120 Corresponding_Record_Type
(Ptyp
);
2121 Next_Entity
(Task_Proc
);
2124 if Present
(Task_Proc
) then
2125 Set_Entity
(Pref
, Task_Proc
);
2126 Set_Etype
(Pref
, Etype
(Task_Proc
));
2129 -- Similarly, the address of a protected operation is the address
2130 -- of the corresponding protected body, regardless of the protected
2131 -- object from which it is selected.
2133 elsif Nkind
(Pref
) = N_Selected_Component
2134 and then Is_Subprogram
(Entity
(Selector_Name
(Pref
)))
2135 and then Is_Protected_Type
(Scope
(Entity
(Selector_Name
(Pref
))))
2139 External_Subprogram
(Entity
(Selector_Name
(Pref
))), Loc
));
2141 elsif Nkind
(Pref
) = N_Explicit_Dereference
2142 and then Ekind
(Ptyp
) = E_Subprogram_Type
2143 and then Convention
(Ptyp
) = Convention_Protected
2145 -- The prefix is be a dereference of an access_to_protected_
2146 -- subprogram. The desired address is the second component of
2147 -- the record that represents the access.
2150 Addr
: constant Entity_Id
:= Etype
(N
);
2151 Ptr
: constant Node_Id
:= Prefix
(Pref
);
2152 T
: constant Entity_Id
:=
2153 Equivalent_Type
(Base_Type
(Etype
(Ptr
)));
2157 Unchecked_Convert_To
(Addr
,
2158 Make_Selected_Component
(Loc
,
2159 Prefix
=> Unchecked_Convert_To
(T
, Ptr
),
2160 Selector_Name
=> New_Occurrence_Of
(
2161 Next_Entity
(First_Entity
(T
)), Loc
))));
2163 Analyze_And_Resolve
(N
, Addr
);
2166 -- Ada 2005 (AI-251): Class-wide interface objects are always
2167 -- "displaced" to reference the tag associated with the interface
2168 -- type. In order to obtain the real address of such objects we
2169 -- generate a call to a run-time subprogram that returns the base
2170 -- address of the object.
2172 -- This processing is not needed in the VM case, where dispatching
2173 -- issues are taken care of by the virtual machine.
2175 elsif Is_Class_Wide_Type
(Ptyp
)
2176 and then Is_Interface
(Ptyp
)
2177 and then Tagged_Type_Expansion
2178 and then not (Nkind
(Pref
) in N_Has_Entity
2179 and then Is_Subprogram
(Entity
(Pref
)))
2182 Make_Function_Call
(Loc
,
2183 Name
=> New_Occurrence_Of
(RTE
(RE_Base_Address
), Loc
),
2184 Parameter_Associations
=> New_List
(
2185 Relocate_Node
(N
))));
2190 -- Deal with packed array reference, other cases are handled by
2193 if Involves_Packed_Array_Reference
(Pref
) then
2194 Expand_Packed_Address_Reference
(N
);
2202 when Attribute_Alignment
=> Alignment
: declare
2206 -- For class-wide types, X'Class'Alignment is transformed into a
2207 -- direct reference to the Alignment of the class type, so that the
2208 -- back end does not have to deal with the X'Class'Alignment
2211 if Is_Entity_Name
(Pref
)
2212 and then Is_Class_Wide_Type
(Entity
(Pref
))
2214 Rewrite
(Prefix
(N
), New_Occurrence_Of
(Entity
(Pref
), Loc
));
2217 -- For x'Alignment applied to an object of a class wide type,
2218 -- transform X'Alignment into a call to the predefined primitive
2219 -- operation _Alignment applied to X.
2221 elsif Is_Class_Wide_Type
(Ptyp
) then
2223 Make_Attribute_Reference
(Loc
,
2225 Attribute_Name
=> Name_Tag
);
2227 if VM_Target
= No_VM
then
2228 New_Node
:= Build_Get_Alignment
(Loc
, New_Node
);
2231 Make_Function_Call
(Loc
,
2232 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Alignment
), Loc
),
2233 Parameter_Associations
=> New_List
(New_Node
));
2236 -- Case where the context is a specific integer type with which
2237 -- the original attribute was compatible. The function has a
2238 -- specific type as well, so to preserve the compatibility we
2239 -- must convert explicitly.
2241 if Typ
/= Standard_Integer
then
2242 New_Node
:= Convert_To
(Typ
, New_Node
);
2245 Rewrite
(N
, New_Node
);
2246 Analyze_And_Resolve
(N
, Typ
);
2249 -- For all other cases, we just have to deal with the case of
2250 -- the fact that the result can be universal.
2253 Apply_Universal_Integer_Attribute_Checks
(N
);
2261 -- We compute this if a packed array reference was present, otherwise we
2262 -- leave the computation up to the back end.
2264 when Attribute_Bit
=>
2265 if Involves_Packed_Array_Reference
(Pref
) then
2266 Expand_Packed_Bit_Reference
(N
);
2268 Apply_Universal_Integer_Attribute_Checks
(N
);
2275 -- We compute this if a component clause was present, otherwise we leave
2276 -- the computation up to the back end, since we don't know what layout
2279 -- Note that the attribute can apply to a naked record component
2280 -- in generated code (i.e. the prefix is an identifier that
2281 -- references the component or discriminant entity).
2283 when Attribute_Bit_Position
=> Bit_Position
: declare
2287 if Nkind
(Pref
) = N_Identifier
then
2288 CE
:= Entity
(Pref
);
2290 CE
:= Entity
(Selector_Name
(Pref
));
2293 if Known_Static_Component_Bit_Offset
(CE
) then
2295 Make_Integer_Literal
(Loc
,
2296 Intval
=> Component_Bit_Offset
(CE
)));
2297 Analyze_And_Resolve
(N
, Typ
);
2300 Apply_Universal_Integer_Attribute_Checks
(N
);
2308 -- A reference to P'Body_Version or P'Version is expanded to
2311 -- pragma Import (C, Vnn, "uuuuT");
2313 -- Get_Version_String (Vnn)
2315 -- where uuuu is the unit name (dots replaced by double underscore)
2316 -- and T is B for the cases of Body_Version, or Version applied to a
2317 -- subprogram acting as its own spec, and S for Version applied to a
2318 -- subprogram spec or package. This sequence of code references the
2319 -- unsigned constant created in the main program by the binder.
2321 -- A special exception occurs for Standard, where the string returned
2322 -- is a copy of the library string in gnatvsn.ads.
2324 when Attribute_Body_Version | Attribute_Version
=> Version
: declare
2325 E
: constant Entity_Id
:= Make_Temporary
(Loc
, 'V');
2330 -- If not library unit, get to containing library unit
2332 Pent
:= Entity
(Pref
);
2333 while Pent
/= Standard_Standard
2334 and then Scope
(Pent
) /= Standard_Standard
2335 and then not Is_Child_Unit
(Pent
)
2337 Pent
:= Scope
(Pent
);
2340 -- Special case Standard and Standard.ASCII
2342 if Pent
= Standard_Standard
or else Pent
= Standard_ASCII
then
2344 Make_String_Literal
(Loc
,
2345 Strval
=> Verbose_Library_Version
));
2350 -- Build required string constant
2352 Get_Name_String
(Get_Unit_Name
(Pent
));
2355 for J
in 1 .. Name_Len
- 2 loop
2356 if Name_Buffer
(J
) = '.' then
2357 Store_String_Chars
("__");
2359 Store_String_Char
(Get_Char_Code
(Name_Buffer
(J
)));
2363 -- Case of subprogram acting as its own spec, always use body
2365 if Nkind
(Declaration_Node
(Pent
)) in N_Subprogram_Specification
2366 and then Nkind
(Parent
(Declaration_Node
(Pent
))) =
2368 and then Acts_As_Spec
(Parent
(Declaration_Node
(Pent
)))
2370 Store_String_Chars
("B");
2372 -- Case of no body present, always use spec
2374 elsif not Unit_Requires_Body
(Pent
) then
2375 Store_String_Chars
("S");
2377 -- Otherwise use B for Body_Version, S for spec
2379 elsif Id
= Attribute_Body_Version
then
2380 Store_String_Chars
("B");
2382 Store_String_Chars
("S");
2386 Lib
.Version_Referenced
(S
);
2388 -- Insert the object declaration
2390 Insert_Actions
(N
, New_List
(
2391 Make_Object_Declaration
(Loc
,
2392 Defining_Identifier
=> E
,
2393 Object_Definition
=>
2394 New_Occurrence_Of
(RTE
(RE_Unsigned
), Loc
))));
2396 -- Set entity as imported with correct external name
2398 Set_Is_Imported
(E
);
2399 Set_Interface_Name
(E
, Make_String_Literal
(Loc
, S
));
2401 -- Set entity as internal to ensure proper Sprint output of its
2402 -- implicit importation.
2404 Set_Is_Internal
(E
);
2406 -- And now rewrite original reference
2409 Make_Function_Call
(Loc
,
2410 Name
=> New_Occurrence_Of
(RTE
(RE_Get_Version_String
), Loc
),
2411 Parameter_Associations
=> New_List
(
2412 New_Occurrence_Of
(E
, Loc
))));
2415 Analyze_And_Resolve
(N
, RTE
(RE_Version_String
));
2422 -- Transforms 'Ceiling into a call to the floating-point attribute
2423 -- function Ceiling in Fat_xxx (where xxx is the root type)
2425 when Attribute_Ceiling
=>
2426 Expand_Fpt_Attribute_R
(N
);
2432 -- Transforms 'Callable attribute into a call to the Callable function
2434 when Attribute_Callable
=> Callable
:
2436 -- We have an object of a task interface class-wide type as a prefix
2437 -- to Callable. Generate:
2438 -- callable (Task_Id (Pref._disp_get_task_id));
2440 if Ada_Version
>= Ada_2005
2441 and then Ekind
(Ptyp
) = E_Class_Wide_Type
2442 and then Is_Interface
(Ptyp
)
2443 and then Is_Task_Interface
(Ptyp
)
2446 Make_Function_Call
(Loc
,
2448 New_Occurrence_Of
(RTE
(RE_Callable
), Loc
),
2449 Parameter_Associations
=> New_List
(
2450 Make_Unchecked_Type_Conversion
(Loc
,
2452 New_Occurrence_Of
(RTE
(RO_ST_Task_Id
), Loc
),
2454 Make_Selected_Component
(Loc
,
2456 New_Copy_Tree
(Pref
),
2458 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
))))));
2462 Build_Call_With_Task
(Pref
, RTE
(RE_Callable
)));
2465 Analyze_And_Resolve
(N
, Standard_Boolean
);
2472 -- Transforms 'Caller attribute into a call to either the
2473 -- Task_Entry_Caller or the Protected_Entry_Caller function.
2475 when Attribute_Caller
=> Caller
: declare
2476 Id_Kind
: constant Entity_Id
:= RTE
(RO_AT_Task_Id
);
2477 Ent
: constant Entity_Id
:= Entity
(Pref
);
2478 Conctype
: constant Entity_Id
:= Scope
(Ent
);
2479 Nest_Depth
: Integer := 0;
2486 if Is_Protected_Type
(Conctype
) then
2487 case Corresponding_Runtime_Package
(Conctype
) is
2488 when System_Tasking_Protected_Objects_Entries
=>
2491 (RTE
(RE_Protected_Entry_Caller
), Loc
);
2493 when System_Tasking_Protected_Objects_Single_Entry
=>
2496 (RTE
(RE_Protected_Single_Entry_Caller
), Loc
);
2499 raise Program_Error
;
2503 Unchecked_Convert_To
(Id_Kind
,
2504 Make_Function_Call
(Loc
,
2506 Parameter_Associations
=> New_List
(
2508 (Find_Protection_Object
(Current_Scope
), Loc
)))));
2513 -- Determine the nesting depth of the E'Caller attribute, that
2514 -- is, how many accept statements are nested within the accept
2515 -- statement for E at the point of E'Caller. The runtime uses
2516 -- this depth to find the specified entry call.
2518 for J
in reverse 0 .. Scope_Stack
.Last
loop
2519 S
:= Scope_Stack
.Table
(J
).Entity
;
2521 -- We should not reach the scope of the entry, as it should
2522 -- already have been checked in Sem_Attr that this attribute
2523 -- reference is within a matching accept statement.
2525 pragma Assert
(S
/= Conctype
);
2530 elsif Is_Entry
(S
) then
2531 Nest_Depth
:= Nest_Depth
+ 1;
2536 Unchecked_Convert_To
(Id_Kind
,
2537 Make_Function_Call
(Loc
,
2539 New_Occurrence_Of
(RTE
(RE_Task_Entry_Caller
), Loc
),
2540 Parameter_Associations
=> New_List
(
2541 Make_Integer_Literal
(Loc
,
2542 Intval
=> Int
(Nest_Depth
))))));
2545 Analyze_And_Resolve
(N
, Id_Kind
);
2552 -- Transforms 'Compose into a call to the floating-point attribute
2553 -- function Compose in Fat_xxx (where xxx is the root type)
2555 -- Note: we strictly should have special code here to deal with the
2556 -- case of absurdly negative arguments (less than Integer'First)
2557 -- which will return a (signed) zero value, but it hardly seems
2558 -- worth the effort. Absurdly large positive arguments will raise
2559 -- constraint error which is fine.
2561 when Attribute_Compose
=>
2562 Expand_Fpt_Attribute_RI
(N
);
2568 when Attribute_Constrained
=> Constrained
: declare
2569 Formal_Ent
: constant Entity_Id
:= Param_Entity
(Pref
);
2571 function Is_Constrained_Aliased_View
(Obj
: Node_Id
) return Boolean;
2572 -- Ada 2005 (AI-363): Returns True if the object name Obj denotes a
2573 -- view of an aliased object whose subtype is constrained.
2575 ---------------------------------
2576 -- Is_Constrained_Aliased_View --
2577 ---------------------------------
2579 function Is_Constrained_Aliased_View
(Obj
: Node_Id
) return Boolean is
2583 if Is_Entity_Name
(Obj
) then
2586 if Present
(Renamed_Object
(E
)) then
2587 return Is_Constrained_Aliased_View
(Renamed_Object
(E
));
2589 return Is_Aliased
(E
) and then Is_Constrained
(Etype
(E
));
2593 return Is_Aliased_View
(Obj
)
2595 (Is_Constrained
(Etype
(Obj
))
2597 (Nkind
(Obj
) = N_Explicit_Dereference
2599 not Object_Type_Has_Constrained_Partial_View
2600 (Typ
=> Base_Type
(Etype
(Obj
)),
2601 Scop
=> Current_Scope
)));
2603 end Is_Constrained_Aliased_View
;
2605 -- Start of processing for Constrained
2608 -- Reference to a parameter where the value is passed as an extra
2609 -- actual, corresponding to the extra formal referenced by the
2610 -- Extra_Constrained field of the corresponding formal. If this
2611 -- is an entry in-parameter, it is replaced by a constant renaming
2612 -- for which Extra_Constrained is never created.
2614 if Present
(Formal_Ent
)
2615 and then Ekind
(Formal_Ent
) /= E_Constant
2616 and then Present
(Extra_Constrained
(Formal_Ent
))
2620 (Extra_Constrained
(Formal_Ent
), Sloc
(N
)));
2622 -- For variables with a Extra_Constrained field, we use the
2623 -- corresponding entity.
2625 elsif Nkind
(Pref
) = N_Identifier
2626 and then Ekind
(Entity
(Pref
)) = E_Variable
2627 and then Present
(Extra_Constrained
(Entity
(Pref
)))
2631 (Extra_Constrained
(Entity
(Pref
)), Sloc
(N
)));
2633 -- For all other entity names, we can tell at compile time
2635 elsif Is_Entity_Name
(Pref
) then
2637 Ent
: constant Entity_Id
:= Entity
(Pref
);
2641 -- (RM J.4) obsolescent cases
2643 if Is_Type
(Ent
) then
2647 if Is_Private_Type
(Ent
) then
2648 Res
:= not Has_Discriminants
(Ent
)
2649 or else Is_Constrained
(Ent
);
2651 -- It not a private type, must be a generic actual type
2652 -- that corresponded to a private type. We know that this
2653 -- correspondence holds, since otherwise the reference
2654 -- within the generic template would have been illegal.
2657 if Is_Composite_Type
(Underlying_Type
(Ent
)) then
2658 Res
:= Is_Constrained
(Ent
);
2664 -- If the prefix is not a variable or is aliased, then
2665 -- definitely true; if it's a formal parameter without an
2666 -- associated extra formal, then treat it as constrained.
2668 -- Ada 2005 (AI-363): An aliased prefix must be known to be
2669 -- constrained in order to set the attribute to True.
2671 elsif not Is_Variable
(Pref
)
2672 or else Present
(Formal_Ent
)
2673 or else (Ada_Version
< Ada_2005
2674 and then Is_Aliased_View
(Pref
))
2675 or else (Ada_Version
>= Ada_2005
2676 and then Is_Constrained_Aliased_View
(Pref
))
2680 -- Variable case, look at type to see if it is constrained.
2681 -- Note that the one case where this is not accurate (the
2682 -- procedure formal case), has been handled above.
2684 -- We use the Underlying_Type here (and below) in case the
2685 -- type is private without discriminants, but the full type
2686 -- has discriminants. This case is illegal, but we generate it
2687 -- internally for passing to the Extra_Constrained parameter.
2690 -- In Ada 2012, test for case of a limited tagged type, in
2691 -- which case the attribute is always required to return
2692 -- True. The underlying type is tested, to make sure we also
2693 -- return True for cases where there is an unconstrained
2694 -- object with an untagged limited partial view which has
2695 -- defaulted discriminants (such objects always produce a
2696 -- False in earlier versions of Ada). (Ada 2012: AI05-0214)
2698 Res
:= Is_Constrained
(Underlying_Type
(Etype
(Ent
)))
2700 (Ada_Version
>= Ada_2012
2701 and then Is_Tagged_Type
(Underlying_Type
(Ptyp
))
2702 and then Is_Limited_Type
(Ptyp
));
2705 Rewrite
(N
, New_Occurrence_Of
(Boolean_Literals
(Res
), Loc
));
2708 -- Prefix is not an entity name. These are also cases where we can
2709 -- always tell at compile time by looking at the form and type of the
2710 -- prefix. If an explicit dereference of an object with constrained
2711 -- partial view, this is unconstrained (Ada 2005: AI95-0363). If the
2712 -- underlying type is a limited tagged type, then Constrained is
2713 -- required to always return True (Ada 2012: AI05-0214).
2719 not Is_Variable
(Pref
)
2721 (Nkind
(Pref
) = N_Explicit_Dereference
2723 not Object_Type_Has_Constrained_Partial_View
2724 (Typ
=> Base_Type
(Ptyp
),
2725 Scop
=> Current_Scope
))
2726 or else Is_Constrained
(Underlying_Type
(Ptyp
))
2727 or else (Ada_Version
>= Ada_2012
2728 and then Is_Tagged_Type
(Underlying_Type
(Ptyp
))
2729 and then Is_Limited_Type
(Ptyp
))),
2733 Analyze_And_Resolve
(N
, Standard_Boolean
);
2740 -- Transforms 'Copy_Sign into a call to the floating-point attribute
2741 -- function Copy_Sign in Fat_xxx (where xxx is the root type)
2743 when Attribute_Copy_Sign
=>
2744 Expand_Fpt_Attribute_RR
(N
);
2750 -- Transforms 'Count attribute into a call to the Count function
2752 when Attribute_Count
=> Count
: declare
2754 Conctyp
: Entity_Id
;
2756 Entry_Id
: Entity_Id
;
2761 -- If the prefix is a member of an entry family, retrieve both
2762 -- entry name and index. For a simple entry there is no index.
2764 if Nkind
(Pref
) = N_Indexed_Component
then
2765 Entnam
:= Prefix
(Pref
);
2766 Index
:= First
(Expressions
(Pref
));
2772 Entry_Id
:= Entity
(Entnam
);
2774 -- Find the concurrent type in which this attribute is referenced
2775 -- (there had better be one).
2777 Conctyp
:= Current_Scope
;
2778 while not Is_Concurrent_Type
(Conctyp
) loop
2779 Conctyp
:= Scope
(Conctyp
);
2784 if Is_Protected_Type
(Conctyp
) then
2785 case Corresponding_Runtime_Package
(Conctyp
) is
2786 when System_Tasking_Protected_Objects_Entries
=>
2787 Name
:= New_Occurrence_Of
(RTE
(RE_Protected_Count
), Loc
);
2790 Make_Function_Call
(Loc
,
2792 Parameter_Associations
=> New_List
(
2794 (Find_Protection_Object
(Current_Scope
), Loc
),
2795 Entry_Index_Expression
2796 (Loc
, Entry_Id
, Index
, Scope
(Entry_Id
))));
2798 when System_Tasking_Protected_Objects_Single_Entry
=>
2800 New_Occurrence_Of
(RTE
(RE_Protected_Count_Entry
), Loc
);
2803 Make_Function_Call
(Loc
,
2805 Parameter_Associations
=> New_List
(
2807 (Find_Protection_Object
(Current_Scope
), Loc
)));
2810 raise Program_Error
;
2817 Make_Function_Call
(Loc
,
2818 Name
=> New_Occurrence_Of
(RTE
(RE_Task_Count
), Loc
),
2819 Parameter_Associations
=> New_List
(
2820 Entry_Index_Expression
(Loc
,
2821 Entry_Id
, Index
, Scope
(Entry_Id
))));
2824 -- The call returns type Natural but the context is universal integer
2825 -- so any integer type is allowed. The attribute was already resolved
2826 -- so its Etype is the required result type. If the base type of the
2827 -- context type is other than Standard.Integer we put in a conversion
2828 -- to the required type. This can be a normal typed conversion since
2829 -- both input and output types of the conversion are integer types
2831 if Base_Type
(Typ
) /= Base_Type
(Standard_Integer
) then
2832 Rewrite
(N
, Convert_To
(Typ
, Call
));
2837 Analyze_And_Resolve
(N
, Typ
);
2840 ---------------------
2841 -- Descriptor_Size --
2842 ---------------------
2844 when Attribute_Descriptor_Size
=>
2846 -- Attribute Descriptor_Size is handled by the back end when applied
2847 -- to an unconstrained array type.
2849 if Is_Array_Type
(Ptyp
)
2850 and then not Is_Constrained
(Ptyp
)
2852 Apply_Universal_Integer_Attribute_Checks
(N
);
2854 -- For any other type, the descriptor size is 0 because there is no
2855 -- actual descriptor, but the result is not formally static.
2858 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
2860 Set_Is_Static_Expression
(N
, False);
2867 -- This processing is shared by Elab_Spec
2869 -- What we do is to insert the following declarations
2872 -- pragma Import (C, enn, "name___elabb/s");
2874 -- and then the Elab_Body/Spec attribute is replaced by a reference
2875 -- to this defining identifier.
2877 when Attribute_Elab_Body |
2878 Attribute_Elab_Spec
=>
2880 -- Leave attribute unexpanded in CodePeer mode: the gnat2scil
2881 -- back-end knows how to handle these attributes directly.
2883 if CodePeer_Mode
then
2888 Ent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'E');
2892 procedure Make_Elab_String
(Nod
: Node_Id
);
2893 -- Given Nod, an identifier, or a selected component, put the
2894 -- image into the current string literal, with double underline
2895 -- between components.
2897 ----------------------
2898 -- Make_Elab_String --
2899 ----------------------
2901 procedure Make_Elab_String
(Nod
: Node_Id
) is
2903 if Nkind
(Nod
) = N_Selected_Component
then
2904 Make_Elab_String
(Prefix
(Nod
));
2908 Store_String_Char
('$');
2910 Store_String_Char
('.');
2912 Store_String_Char
('_');
2913 Store_String_Char
('_');
2916 Get_Name_String
(Chars
(Selector_Name
(Nod
)));
2919 pragma Assert
(Nkind
(Nod
) = N_Identifier
);
2920 Get_Name_String
(Chars
(Nod
));
2923 Store_String_Chars
(Name_Buffer
(1 .. Name_Len
));
2924 end Make_Elab_String
;
2926 -- Start of processing for Elab_Body/Elab_Spec
2929 -- First we need to prepare the string literal for the name of
2930 -- the elaboration routine to be referenced.
2933 Make_Elab_String
(Pref
);
2935 if VM_Target
= No_VM
then
2936 Store_String_Chars
("___elab");
2937 Lang
:= Make_Identifier
(Loc
, Name_C
);
2939 Store_String_Chars
("._elab");
2940 Lang
:= Make_Identifier
(Loc
, Name_Ada
);
2943 if Id
= Attribute_Elab_Body
then
2944 Store_String_Char
('b');
2946 Store_String_Char
('s');
2951 Insert_Actions
(N
, New_List
(
2952 Make_Subprogram_Declaration
(Loc
,
2954 Make_Procedure_Specification
(Loc
,
2955 Defining_Unit_Name
=> Ent
)),
2958 Chars
=> Name_Import
,
2959 Pragma_Argument_Associations
=> New_List
(
2960 Make_Pragma_Argument_Association
(Loc
, Expression
=> Lang
),
2962 Make_Pragma_Argument_Association
(Loc
,
2963 Expression
=> Make_Identifier
(Loc
, Chars
(Ent
))),
2965 Make_Pragma_Argument_Association
(Loc
,
2966 Expression
=> Make_String_Literal
(Loc
, Str
))))));
2968 Set_Entity
(N
, Ent
);
2969 Rewrite
(N
, New_Occurrence_Of
(Ent
, Loc
));
2972 --------------------
2973 -- Elab_Subp_Body --
2974 --------------------
2976 -- Always ignored. In CodePeer mode, gnat2scil knows how to handle
2977 -- this attribute directly, and if we are not in CodePeer mode it is
2978 -- entirely ignored ???
2980 when Attribute_Elab_Subp_Body
=>
2987 -- Elaborated is always True for preelaborated units, predefined units,
2988 -- pure units and units which have Elaborate_Body pragmas. These units
2989 -- have no elaboration entity.
2991 -- Note: The Elaborated attribute is never passed to the back end
2993 when Attribute_Elaborated
=> Elaborated
: declare
2994 Ent
: constant Entity_Id
:= Entity
(Pref
);
2997 if Present
(Elaboration_Entity
(Ent
)) then
3001 New_Occurrence_Of
(Elaboration_Entity
(Ent
), Loc
),
3003 Make_Integer_Literal
(Loc
, Uint_0
)));
3004 Analyze_And_Resolve
(N
, Typ
);
3006 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
3014 when Attribute_Enum_Rep
=> Enum_Rep
:
3016 -- X'Enum_Rep (Y) expands to
3020 -- This is simply a direct conversion from the enumeration type to
3021 -- the target integer type, which is treated by the back end as a
3022 -- normal integer conversion, treating the enumeration type as an
3023 -- integer, which is exactly what we want. We set Conversion_OK to
3024 -- make sure that the analyzer does not complain about what otherwise
3025 -- might be an illegal conversion.
3027 if Is_Non_Empty_List
(Exprs
) then
3029 OK_Convert_To
(Typ
, Relocate_Node
(First
(Exprs
))));
3031 -- X'Enum_Rep where X is an enumeration literal is replaced by
3032 -- the literal value.
3034 elsif Ekind
(Entity
(Pref
)) = E_Enumeration_Literal
then
3036 Make_Integer_Literal
(Loc
, Enumeration_Rep
(Entity
(Pref
))));
3038 -- If this is a renaming of a literal, recover the representation
3041 elsif Ekind
(Entity
(Pref
)) = E_Constant
3042 and then Present
(Renamed_Object
(Entity
(Pref
)))
3044 Ekind
(Entity
(Renamed_Object
(Entity
(Pref
))))
3045 = E_Enumeration_Literal
3048 Make_Integer_Literal
(Loc
,
3049 Enumeration_Rep
(Entity
(Renamed_Object
(Entity
(Pref
))))));
3051 -- X'Enum_Rep where X is an object does a direct unchecked conversion
3052 -- of the object value, as described for the type case above.
3056 OK_Convert_To
(Typ
, Relocate_Node
(Pref
)));
3060 Analyze_And_Resolve
(N
, Typ
);
3067 when Attribute_Enum_Val
=> Enum_Val
: declare
3069 Btyp
: constant Entity_Id
:= Base_Type
(Ptyp
);
3072 -- X'Enum_Val (Y) expands to
3074 -- [constraint_error when _rep_to_pos (Y, False) = -1, msg]
3077 Expr
:= Unchecked_Convert_To
(Ptyp
, First
(Exprs
));
3080 Make_Raise_Constraint_Error
(Loc
,
3084 Make_Function_Call
(Loc
,
3086 New_Occurrence_Of
(TSS
(Btyp
, TSS_Rep_To_Pos
), Loc
),
3087 Parameter_Associations
=> New_List
(
3088 Relocate_Node
(Duplicate_Subexpr
(Expr
)),
3089 New_Occurrence_Of
(Standard_False
, Loc
))),
3091 Right_Opnd
=> Make_Integer_Literal
(Loc
, -1)),
3092 Reason
=> CE_Range_Check_Failed
));
3095 Analyze_And_Resolve
(N
, Ptyp
);
3102 -- Transforms 'Exponent into a call to the floating-point attribute
3103 -- function Exponent in Fat_xxx (where xxx is the root type)
3105 when Attribute_Exponent
=>
3106 Expand_Fpt_Attribute_R
(N
);
3112 -- transforme X'External_Tag into Ada.Tags.External_Tag (X'tag)
3114 when Attribute_External_Tag
=> External_Tag
:
3117 Make_Function_Call
(Loc
,
3118 Name
=> New_Occurrence_Of
(RTE
(RE_External_Tag
), Loc
),
3119 Parameter_Associations
=> New_List
(
3120 Make_Attribute_Reference
(Loc
,
3121 Attribute_Name
=> Name_Tag
,
3122 Prefix
=> Prefix
(N
)))));
3124 Analyze_And_Resolve
(N
, Standard_String
);
3131 when Attribute_First
=>
3133 -- If the prefix type is a constrained packed array type which
3134 -- already has a Packed_Array_Impl_Type representation defined, then
3135 -- replace this attribute with a direct reference to 'First of the
3136 -- appropriate index subtype (since otherwise the back end will try
3137 -- to give us the value of 'First for this implementation type).
3139 if Is_Constrained_Packed_Array
(Ptyp
) then
3141 Make_Attribute_Reference
(Loc
,
3142 Attribute_Name
=> Name_First
,
3144 New_Occurrence_Of
(Get_Index_Subtype
(N
), Loc
)));
3145 Analyze_And_Resolve
(N
, Typ
);
3147 -- For access type, apply access check as needed
3149 elsif Is_Access_Type
(Ptyp
) then
3150 Apply_Access_Check
(N
);
3152 -- For scalar type, if low bound is a reference to an entity, just
3153 -- replace with a direct reference. Note that we can only have a
3154 -- reference to a constant entity at this stage, anything else would
3155 -- have already been rewritten.
3157 elsif Is_Scalar_Type
(Ptyp
) then
3159 Lo
: constant Node_Id
:= Type_Low_Bound
(Ptyp
);
3161 if Is_Entity_Name
(Lo
) then
3162 Rewrite
(N
, New_Occurrence_Of
(Entity
(Lo
), Loc
));
3171 -- Compute this if component clause was present, otherwise we leave the
3172 -- computation to be completed in the back-end, since we don't know what
3173 -- layout will be chosen.
3175 when Attribute_First_Bit
=> First_Bit_Attr
: declare
3176 CE
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
3179 -- In Ada 2005 (or later) if we have the non-default bit order, then
3180 -- we return the original value as given in the component clause
3181 -- (RM 2005 13.5.2(3/2)).
3183 if Present
(Component_Clause
(CE
))
3184 and then Ada_Version
>= Ada_2005
3185 and then Reverse_Bit_Order
(Scope
(CE
))
3188 Make_Integer_Literal
(Loc
,
3189 Intval
=> Expr_Value
(First_Bit
(Component_Clause
(CE
)))));
3190 Analyze_And_Resolve
(N
, Typ
);
3192 -- Otherwise (Ada 83/95 or Ada 2005 or later with default bit order),
3193 -- rewrite with normalized value if we know it statically.
3195 elsif Known_Static_Component_Bit_Offset
(CE
) then
3197 Make_Integer_Literal
(Loc
,
3198 Component_Bit_Offset
(CE
) mod System_Storage_Unit
));
3199 Analyze_And_Resolve
(N
, Typ
);
3201 -- Otherwise left to back end, just do universal integer checks
3204 Apply_Universal_Integer_Attribute_Checks
(N
);
3214 -- fixtype'Fixed_Value (integer-value)
3218 -- fixtype(integer-value)
3220 -- We do all the required analysis of the conversion here, because we do
3221 -- not want this to go through the fixed-point conversion circuits. Note
3222 -- that the back end always treats fixed-point as equivalent to the
3223 -- corresponding integer type anyway.
3225 when Attribute_Fixed_Value
=> Fixed_Value
:
3228 Make_Type_Conversion
(Loc
,
3229 Subtype_Mark
=> New_Occurrence_Of
(Entity
(Pref
), Loc
),
3230 Expression
=> Relocate_Node
(First
(Exprs
))));
3231 Set_Etype
(N
, Entity
(Pref
));
3234 -- Note: it might appear that a properly analyzed unchecked conversion
3235 -- would be just fine here, but that's not the case, since the full
3236 -- range checks performed by the following call are critical.
3238 Apply_Type_Conversion_Checks
(N
);
3245 -- Transforms 'Floor into a call to the floating-point attribute
3246 -- function Floor in Fat_xxx (where xxx is the root type)
3248 when Attribute_Floor
=>
3249 Expand_Fpt_Attribute_R
(N
);
3255 -- For the fixed-point type Typ:
3261 -- Result_Type (System.Fore (Universal_Real (Type'First)),
3262 -- Universal_Real (Type'Last))
3264 -- Note that we know that the type is a non-static subtype, or Fore
3265 -- would have itself been computed dynamically in Eval_Attribute.
3267 when Attribute_Fore
=> Fore
: begin
3270 Make_Function_Call
(Loc
,
3271 Name
=> New_Occurrence_Of
(RTE
(RE_Fore
), Loc
),
3273 Parameter_Associations
=> New_List
(
3274 Convert_To
(Universal_Real
,
3275 Make_Attribute_Reference
(Loc
,
3276 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
3277 Attribute_Name
=> Name_First
)),
3279 Convert_To
(Universal_Real
,
3280 Make_Attribute_Reference
(Loc
,
3281 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
3282 Attribute_Name
=> Name_Last
))))));
3284 Analyze_And_Resolve
(N
, Typ
);
3291 -- Transforms 'Fraction into a call to the floating-point attribute
3292 -- function Fraction in Fat_xxx (where xxx is the root type)
3294 when Attribute_Fraction
=>
3295 Expand_Fpt_Attribute_R
(N
);
3301 when Attribute_From_Any
=> From_Any
: declare
3302 P_Type
: constant Entity_Id
:= Etype
(Pref
);
3303 Decls
: constant List_Id
:= New_List
;
3306 Build_From_Any_Call
(P_Type
,
3307 Relocate_Node
(First
(Exprs
)),
3309 Insert_Actions
(N
, Decls
);
3310 Analyze_And_Resolve
(N
, P_Type
);
3313 ----------------------
3314 -- Has_Same_Storage --
3315 ----------------------
3317 when Attribute_Has_Same_Storage
=> Has_Same_Storage
: declare
3318 Loc
: constant Source_Ptr
:= Sloc
(N
);
3320 X
: constant Node_Id
:= Prefix
(N
);
3321 Y
: constant Node_Id
:= First
(Expressions
(N
));
3324 X_Addr
, Y_Addr
: Node_Id
;
3325 -- Rhe expressions for their addresses
3327 X_Size
, Y_Size
: Node_Id
;
3328 -- Rhe expressions for their sizes
3331 -- The attribute is expanded as:
3333 -- (X'address = Y'address)
3334 -- and then (X'Size = Y'Size)
3336 -- If both arguments have the same Etype the second conjunct can be
3340 Make_Attribute_Reference
(Loc
,
3341 Attribute_Name
=> Name_Address
,
3342 Prefix
=> New_Copy_Tree
(X
));
3345 Make_Attribute_Reference
(Loc
,
3346 Attribute_Name
=> Name_Address
,
3347 Prefix
=> New_Copy_Tree
(Y
));
3350 Make_Attribute_Reference
(Loc
,
3351 Attribute_Name
=> Name_Size
,
3352 Prefix
=> New_Copy_Tree
(X
));
3355 Make_Attribute_Reference
(Loc
,
3356 Attribute_Name
=> Name_Size
,
3357 Prefix
=> New_Copy_Tree
(Y
));
3359 if Etype
(X
) = Etype
(Y
) then
3362 Left_Opnd
=> X_Addr
,
3363 Right_Opnd
=> Y_Addr
)));
3369 Left_Opnd
=> X_Addr
,
3370 Right_Opnd
=> Y_Addr
),
3373 Left_Opnd
=> X_Size
,
3374 Right_Opnd
=> Y_Size
)));
3377 Analyze_And_Resolve
(N
, Standard_Boolean
);
3378 end Has_Same_Storage
;
3384 -- For an exception returns a reference to the exception data:
3385 -- Exception_Id!(Prefix'Reference)
3387 -- For a task it returns a reference to the _task_id component of
3388 -- corresponding record:
3390 -- taskV!(Prefix)._Task_Id, converted to the type Task_Id defined
3392 -- in Ada.Task_Identification
3394 when Attribute_Identity
=> Identity
: declare
3395 Id_Kind
: Entity_Id
;
3398 if Ptyp
= Standard_Exception_Type
then
3399 Id_Kind
:= RTE
(RE_Exception_Id
);
3401 if Present
(Renamed_Object
(Entity
(Pref
))) then
3402 Set_Entity
(Pref
, Renamed_Object
(Entity
(Pref
)));
3406 Unchecked_Convert_To
(Id_Kind
, Make_Reference
(Loc
, Pref
)));
3408 Id_Kind
:= RTE
(RO_AT_Task_Id
);
3410 -- If the prefix is a task interface, the Task_Id is obtained
3411 -- dynamically through a dispatching call, as for other task
3412 -- attributes applied to interfaces.
3414 if Ada_Version
>= Ada_2005
3415 and then Ekind
(Ptyp
) = E_Class_Wide_Type
3416 and then Is_Interface
(Ptyp
)
3417 and then Is_Task_Interface
(Ptyp
)
3420 Unchecked_Convert_To
(Id_Kind
,
3421 Make_Selected_Component
(Loc
,
3423 New_Copy_Tree
(Pref
),
3425 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
))));
3429 Unchecked_Convert_To
(Id_Kind
, Concurrent_Ref
(Pref
)));
3433 Analyze_And_Resolve
(N
, Id_Kind
);
3440 -- Image attribute is handled in separate unit Exp_Imgv
3442 when Attribute_Image
=>
3443 Exp_Imgv
.Expand_Image_Attribute
(N
);
3449 -- X'Img is expanded to typ'Image (X), where typ is the type of X
3451 when Attribute_Img
=> Img
:
3454 Make_Attribute_Reference
(Loc
,
3455 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
3456 Attribute_Name
=> Name_Image
,
3457 Expressions
=> New_List
(Relocate_Node
(Pref
))));
3459 Analyze_And_Resolve
(N
, Standard_String
);
3466 when Attribute_Input
=> Input
: declare
3467 P_Type
: constant Entity_Id
:= Entity
(Pref
);
3468 B_Type
: constant Entity_Id
:= Base_Type
(P_Type
);
3469 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
3470 Strm
: constant Node_Id
:= First
(Exprs
);
3478 Cntrl
: Node_Id
:= Empty
;
3479 -- Value for controlling argument in call. Always Empty except in
3480 -- the dispatching (class-wide type) case, where it is a reference
3481 -- to the dummy object initialized to the right internal tag.
3483 procedure Freeze_Stream_Subprogram
(F
: Entity_Id
);
3484 -- The expansion of the attribute reference may generate a call to
3485 -- a user-defined stream subprogram that is frozen by the call. This
3486 -- can lead to access-before-elaboration problem if the reference
3487 -- appears in an object declaration and the subprogram body has not
3488 -- been seen. The freezing of the subprogram requires special code
3489 -- because it appears in an expanded context where expressions do
3490 -- not freeze their constituents.
3492 ------------------------------
3493 -- Freeze_Stream_Subprogram --
3494 ------------------------------
3496 procedure Freeze_Stream_Subprogram
(F
: Entity_Id
) is
3497 Decl
: constant Node_Id
:= Unit_Declaration_Node
(F
);
3501 -- If this is user-defined subprogram, the corresponding
3502 -- stream function appears as a renaming-as-body, and the
3503 -- user subprogram must be retrieved by tree traversal.
3506 and then Nkind
(Decl
) = N_Subprogram_Declaration
3507 and then Present
(Corresponding_Body
(Decl
))
3509 Bod
:= Corresponding_Body
(Decl
);
3511 if Nkind
(Unit_Declaration_Node
(Bod
)) =
3512 N_Subprogram_Renaming_Declaration
3514 Set_Is_Frozen
(Entity
(Name
(Unit_Declaration_Node
(Bod
))));
3517 end Freeze_Stream_Subprogram
;
3519 -- Start of processing for Input
3522 -- If no underlying type, we have an error that will be diagnosed
3523 -- elsewhere, so here we just completely ignore the expansion.
3529 -- Stream operations can appear in user code even if the restriction
3530 -- No_Streams is active (for example, when instantiating a predefined
3531 -- container). In that case rewrite the attribute as a Raise to
3532 -- prevent any run-time use.
3534 if Restriction_Active
(No_Streams
) then
3536 Make_Raise_Program_Error
(Sloc
(N
),
3537 Reason
=> PE_Stream_Operation_Not_Allowed
));
3538 Set_Etype
(N
, B_Type
);
3542 -- If there is a TSS for Input, just call it
3544 Fname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Input
);
3546 if Present
(Fname
) then
3550 -- If there is a Stream_Convert pragma, use it, we rewrite
3552 -- sourcetyp'Input (stream)
3556 -- sourcetyp (streamread (strmtyp'Input (stream)));
3558 -- where streamread is the given Read function that converts an
3559 -- argument of type strmtyp to type sourcetyp or a type from which
3560 -- it is derived (extra conversion required for the derived case).
3562 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
3564 if Present
(Prag
) then
3565 Arg2
:= Next
(First
(Pragma_Argument_Associations
(Prag
)));
3566 Rfunc
:= Entity
(Expression
(Arg2
));
3570 Make_Function_Call
(Loc
,
3571 Name
=> New_Occurrence_Of
(Rfunc
, Loc
),
3572 Parameter_Associations
=> New_List
(
3573 Make_Attribute_Reference
(Loc
,
3576 (Etype
(First_Formal
(Rfunc
)), Loc
),
3577 Attribute_Name
=> Name_Input
,
3578 Expressions
=> Exprs
)))));
3580 Analyze_And_Resolve
(N
, B_Type
);
3585 elsif Is_Elementary_Type
(U_Type
) then
3587 -- A special case arises if we have a defined _Read routine,
3588 -- since in this case we are required to call this routine.
3590 if Present
(TSS
(Base_Type
(U_Type
), TSS_Stream_Read
)) then
3591 Build_Record_Or_Elementary_Input_Function
3592 (Loc
, U_Type
, Decl
, Fname
);
3593 Insert_Action
(N
, Decl
);
3595 -- For normal cases, we call the I_xxx routine directly
3598 Rewrite
(N
, Build_Elementary_Input_Call
(N
));
3599 Analyze_And_Resolve
(N
, P_Type
);
3605 elsif Is_Array_Type
(U_Type
) then
3606 Build_Array_Input_Function
(Loc
, U_Type
, Decl
, Fname
);
3607 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
3609 -- Dispatching case with class-wide type
3611 elsif Is_Class_Wide_Type
(P_Type
) then
3613 -- No need to do anything else compiling under restriction
3614 -- No_Dispatching_Calls. During the semantic analysis we
3615 -- already notified such violation.
3617 if Restriction_Active
(No_Dispatching_Calls
) then
3622 Rtyp
: constant Entity_Id
:= Root_Type
(P_Type
);
3628 -- Read the internal tag (RM 13.13.2(34)) and use it to
3629 -- initialize a dummy tag object:
3631 -- Dnn : Ada.Tags.Tag :=
3632 -- Descendant_Tag (String'Input (Strm), P_Type);
3634 -- This dummy object is used only to provide a controlling
3635 -- argument for the eventual _Input call. Descendant_Tag is
3636 -- called rather than Internal_Tag to ensure that we have a
3637 -- tag for a type that is descended from the prefix type and
3638 -- declared at the same accessibility level (the exception
3639 -- Tag_Error will be raised otherwise). The level check is
3640 -- required for Ada 2005 because tagged types can be
3641 -- extended in nested scopes (AI-344).
3644 Make_Function_Call
(Loc
,
3646 New_Occurrence_Of
(RTE
(RE_Descendant_Tag
), Loc
),
3647 Parameter_Associations
=> New_List
(
3648 Make_Attribute_Reference
(Loc
,
3649 Prefix
=> New_Occurrence_Of
(Standard_String
, Loc
),
3650 Attribute_Name
=> Name_Input
,
3651 Expressions
=> New_List
(
3652 Relocate_Node
(Duplicate_Subexpr
(Strm
)))),
3653 Make_Attribute_Reference
(Loc
,
3654 Prefix
=> New_Occurrence_Of
(P_Type
, Loc
),
3655 Attribute_Name
=> Name_Tag
)));
3657 Dnn
:= Make_Temporary
(Loc
, 'D', Expr
);
3660 Make_Object_Declaration
(Loc
,
3661 Defining_Identifier
=> Dnn
,
3662 Object_Definition
=>
3663 New_Occurrence_Of
(RTE
(RE_Tag
), Loc
),
3664 Expression
=> Expr
);
3666 Insert_Action
(N
, Decl
);
3668 -- Now we need to get the entity for the call, and construct
3669 -- a function call node, where we preset a reference to Dnn
3670 -- as the controlling argument (doing an unchecked convert
3671 -- to the class-wide tagged type to make it look like a real
3674 Fname
:= Find_Prim_Op
(Rtyp
, TSS_Stream_Input
);
3676 Unchecked_Convert_To
(P_Type
,
3677 New_Occurrence_Of
(Dnn
, Loc
));
3678 Set_Etype
(Cntrl
, P_Type
);
3679 Set_Parent
(Cntrl
, N
);
3682 -- For tagged types, use the primitive Input function
3684 elsif Is_Tagged_Type
(U_Type
) then
3685 Fname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Input
);
3687 -- All other record type cases, including protected records. The
3688 -- latter only arise for expander generated code for handling
3689 -- shared passive partition access.
3693 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
3695 -- Ada 2005 (AI-216): Program_Error is raised executing default
3696 -- implementation of the Input attribute of an unchecked union
3697 -- type if the type lacks default discriminant values.
3699 if Is_Unchecked_Union
(Base_Type
(U_Type
))
3700 and then No
(Discriminant_Constraint
(U_Type
))
3703 Make_Raise_Program_Error
(Loc
,
3704 Reason
=> PE_Unchecked_Union_Restriction
));
3709 -- Build the type's Input function, passing the subtype rather
3710 -- than its base type, because checks are needed in the case of
3711 -- constrained discriminants (see Ada 2012 AI05-0192).
3713 Build_Record_Or_Elementary_Input_Function
3714 (Loc
, U_Type
, Decl
, Fname
);
3715 Insert_Action
(N
, Decl
);
3717 if Nkind
(Parent
(N
)) = N_Object_Declaration
3718 and then Is_Record_Type
(U_Type
)
3720 -- The stream function may contain calls to user-defined
3721 -- Read procedures for individual components.
3728 Comp
:= First_Component
(U_Type
);
3729 while Present
(Comp
) loop
3731 Find_Stream_Subprogram
3732 (Etype
(Comp
), TSS_Stream_Read
);
3734 if Present
(Func
) then
3735 Freeze_Stream_Subprogram
(Func
);
3738 Next_Component
(Comp
);
3745 -- If we fall through, Fname is the function to be called. The result
3746 -- is obtained by calling the appropriate function, then converting
3747 -- the result. The conversion does a subtype check.
3750 Make_Function_Call
(Loc
,
3751 Name
=> New_Occurrence_Of
(Fname
, Loc
),
3752 Parameter_Associations
=> New_List
(
3753 Relocate_Node
(Strm
)));
3755 Set_Controlling_Argument
(Call
, Cntrl
);
3756 Rewrite
(N
, Unchecked_Convert_To
(P_Type
, Call
));
3757 Analyze_And_Resolve
(N
, P_Type
);
3759 if Nkind
(Parent
(N
)) = N_Object_Declaration
then
3760 Freeze_Stream_Subprogram
(Fname
);
3770 -- inttype'Fixed_Value (fixed-value)
3774 -- inttype(integer-value))
3776 -- we do all the required analysis of the conversion here, because we do
3777 -- not want this to go through the fixed-point conversion circuits. Note
3778 -- that the back end always treats fixed-point as equivalent to the
3779 -- corresponding integer type anyway.
3781 when Attribute_Integer_Value
=> Integer_Value
:
3784 Make_Type_Conversion
(Loc
,
3785 Subtype_Mark
=> New_Occurrence_Of
(Entity
(Pref
), Loc
),
3786 Expression
=> Relocate_Node
(First
(Exprs
))));
3787 Set_Etype
(N
, Entity
(Pref
));
3790 -- Note: it might appear that a properly analyzed unchecked conversion
3791 -- would be just fine here, but that's not the case, since the full
3792 -- range checks performed by the following call are critical.
3794 Apply_Type_Conversion_Checks
(N
);
3801 when Attribute_Invalid_Value
=>
3802 Rewrite
(N
, Get_Simple_Init_Val
(Ptyp
, N
));
3808 when Attribute_Last
=>
3810 -- If the prefix type is a constrained packed array type which
3811 -- already has a Packed_Array_Impl_Type representation defined, then
3812 -- replace this attribute with a direct reference to 'Last of the
3813 -- appropriate index subtype (since otherwise the back end will try
3814 -- to give us the value of 'Last for this implementation type).
3816 if Is_Constrained_Packed_Array
(Ptyp
) then
3818 Make_Attribute_Reference
(Loc
,
3819 Attribute_Name
=> Name_Last
,
3820 Prefix
=> New_Occurrence_Of
(Get_Index_Subtype
(N
), Loc
)));
3821 Analyze_And_Resolve
(N
, Typ
);
3823 -- For access type, apply access check as needed
3825 elsif Is_Access_Type
(Ptyp
) then
3826 Apply_Access_Check
(N
);
3828 -- For scalar type, if low bound is a reference to an entity, just
3829 -- replace with a direct reference. Note that we can only have a
3830 -- reference to a constant entity at this stage, anything else would
3831 -- have already been rewritten.
3833 elsif Is_Scalar_Type
(Ptyp
) then
3835 Hi
: constant Node_Id
:= Type_High_Bound
(Ptyp
);
3837 if Is_Entity_Name
(Hi
) then
3838 Rewrite
(N
, New_Occurrence_Of
(Entity
(Hi
), Loc
));
3847 -- We compute this if a component clause was present, otherwise we leave
3848 -- the computation up to the back end, since we don't know what layout
3851 when Attribute_Last_Bit
=> Last_Bit_Attr
: declare
3852 CE
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
3855 -- In Ada 2005 (or later) if we have the non-default bit order, then
3856 -- we return the original value as given in the component clause
3857 -- (RM 2005 13.5.2(3/2)).
3859 if Present
(Component_Clause
(CE
))
3860 and then Ada_Version
>= Ada_2005
3861 and then Reverse_Bit_Order
(Scope
(CE
))
3864 Make_Integer_Literal
(Loc
,
3865 Intval
=> Expr_Value
(Last_Bit
(Component_Clause
(CE
)))));
3866 Analyze_And_Resolve
(N
, Typ
);
3868 -- Otherwise (Ada 83/95 or Ada 2005 or later with default bit order),
3869 -- rewrite with normalized value if we know it statically.
3871 elsif Known_Static_Component_Bit_Offset
(CE
)
3872 and then Known_Static_Esize
(CE
)
3875 Make_Integer_Literal
(Loc
,
3876 Intval
=> (Component_Bit_Offset
(CE
) mod System_Storage_Unit
)
3878 Analyze_And_Resolve
(N
, Typ
);
3880 -- Otherwise leave to back end, just apply universal integer checks
3883 Apply_Universal_Integer_Attribute_Checks
(N
);
3891 -- Transforms 'Leading_Part into a call to the floating-point attribute
3892 -- function Leading_Part in Fat_xxx (where xxx is the root type)
3894 -- Note: strictly, we should generate special case code to deal with
3895 -- absurdly large positive arguments (greater than Integer'Last), which
3896 -- result in returning the first argument unchanged, but it hardly seems
3897 -- worth the effort. We raise constraint error for absurdly negative
3898 -- arguments which is fine.
3900 when Attribute_Leading_Part
=>
3901 Expand_Fpt_Attribute_RI
(N
);
3907 when Attribute_Length
=> Length
: declare
3912 -- Processing for packed array types
3914 if Is_Array_Type
(Ptyp
) and then Is_Packed
(Ptyp
) then
3915 Ityp
:= Get_Index_Subtype
(N
);
3917 -- If the index type, Ityp, is an enumeration type with holes,
3918 -- then we calculate X'Length explicitly using
3921 -- (0, Ityp'Pos (X'Last (N)) -
3922 -- Ityp'Pos (X'First (N)) + 1);
3924 -- Since the bounds in the template are the representation values
3925 -- and the back end would get the wrong value.
3927 if Is_Enumeration_Type
(Ityp
)
3928 and then Present
(Enum_Pos_To_Rep
(Base_Type
(Ityp
)))
3933 Xnum
:= Expr_Value
(First
(Expressions
(N
)));
3937 Make_Attribute_Reference
(Loc
,
3938 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
3939 Attribute_Name
=> Name_Max
,
3940 Expressions
=> New_List
3941 (Make_Integer_Literal
(Loc
, 0),
3945 Make_Op_Subtract
(Loc
,
3947 Make_Attribute_Reference
(Loc
,
3948 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
3949 Attribute_Name
=> Name_Pos
,
3951 Expressions
=> New_List
(
3952 Make_Attribute_Reference
(Loc
,
3953 Prefix
=> Duplicate_Subexpr
(Pref
),
3954 Attribute_Name
=> Name_Last
,
3955 Expressions
=> New_List
(
3956 Make_Integer_Literal
(Loc
, Xnum
))))),
3959 Make_Attribute_Reference
(Loc
,
3960 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
3961 Attribute_Name
=> Name_Pos
,
3963 Expressions
=> New_List
(
3964 Make_Attribute_Reference
(Loc
,
3966 Duplicate_Subexpr_No_Checks
(Pref
),
3967 Attribute_Name
=> Name_First
,
3968 Expressions
=> New_List
(
3969 Make_Integer_Literal
(Loc
, Xnum
)))))),
3971 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)))));
3973 Analyze_And_Resolve
(N
, Typ
, Suppress
=> All_Checks
);
3976 -- If the prefix type is a constrained packed array type which
3977 -- already has a Packed_Array_Impl_Type representation defined,
3978 -- then replace this attribute with a reference to 'Range_Length
3979 -- of the appropriate index subtype (since otherwise the
3980 -- back end will try to give us the value of 'Length for
3981 -- this implementation type).s
3983 elsif Is_Constrained
(Ptyp
) then
3985 Make_Attribute_Reference
(Loc
,
3986 Attribute_Name
=> Name_Range_Length
,
3987 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
)));
3988 Analyze_And_Resolve
(N
, Typ
);
3993 elsif Is_Access_Type
(Ptyp
) then
3994 Apply_Access_Check
(N
);
3996 -- If the designated type is a packed array type, then we convert
3997 -- the reference to:
4000 -- xtyp'Pos (Pref'Last (Expr)) -
4001 -- xtyp'Pos (Pref'First (Expr)));
4003 -- This is a bit complex, but it is the easiest thing to do that
4004 -- works in all cases including enum types with holes xtyp here
4005 -- is the appropriate index type.
4008 Dtyp
: constant Entity_Id
:= Designated_Type
(Ptyp
);
4012 if Is_Array_Type
(Dtyp
) and then Is_Packed
(Dtyp
) then
4013 Xtyp
:= Get_Index_Subtype
(N
);
4016 Make_Attribute_Reference
(Loc
,
4017 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
4018 Attribute_Name
=> Name_Max
,
4019 Expressions
=> New_List
(
4020 Make_Integer_Literal
(Loc
, 0),
4023 Make_Integer_Literal
(Loc
, 1),
4024 Make_Op_Subtract
(Loc
,
4026 Make_Attribute_Reference
(Loc
,
4027 Prefix
=> New_Occurrence_Of
(Xtyp
, Loc
),
4028 Attribute_Name
=> Name_Pos
,
4029 Expressions
=> New_List
(
4030 Make_Attribute_Reference
(Loc
,
4031 Prefix
=> Duplicate_Subexpr
(Pref
),
4032 Attribute_Name
=> Name_Last
,
4034 New_Copy_List
(Exprs
)))),
4037 Make_Attribute_Reference
(Loc
,
4038 Prefix
=> New_Occurrence_Of
(Xtyp
, Loc
),
4039 Attribute_Name
=> Name_Pos
,
4040 Expressions
=> New_List
(
4041 Make_Attribute_Reference
(Loc
,
4043 Duplicate_Subexpr_No_Checks
(Pref
),
4044 Attribute_Name
=> Name_First
,
4046 New_Copy_List
(Exprs
)))))))));
4048 Analyze_And_Resolve
(N
, Typ
);
4052 -- Otherwise leave it to the back end
4055 Apply_Universal_Integer_Attribute_Checks
(N
);
4059 -- Attribute Loop_Entry is replaced with a reference to a constant value
4060 -- which captures the prefix at the entry point of the related loop. The
4061 -- loop itself may be transformed into a conditional block.
4063 when Attribute_Loop_Entry
=>
4064 Expand_Loop_Entry_Attribute
(N
);
4070 -- Transforms 'Machine into a call to the floating-point attribute
4071 -- function Machine in Fat_xxx (where xxx is the root type).
4072 -- Expansion is avoided for cases the back end can handle directly.
4074 when Attribute_Machine
=>
4075 if not Is_Inline_Floating_Point_Attribute
(N
) then
4076 Expand_Fpt_Attribute_R
(N
);
4079 ----------------------
4080 -- Machine_Rounding --
4081 ----------------------
4083 -- Transforms 'Machine_Rounding into a call to the floating-point
4084 -- attribute function Machine_Rounding in Fat_xxx (where xxx is the root
4085 -- type). Expansion is avoided for cases the back end can handle
4088 when Attribute_Machine_Rounding
=>
4089 if not Is_Inline_Floating_Point_Attribute
(N
) then
4090 Expand_Fpt_Attribute_R
(N
);
4097 -- Machine_Size is equivalent to Object_Size, so transform it into
4098 -- Object_Size and that way the back end never sees Machine_Size.
4100 when Attribute_Machine_Size
=>
4102 Make_Attribute_Reference
(Loc
,
4103 Prefix
=> Prefix
(N
),
4104 Attribute_Name
=> Name_Object_Size
));
4106 Analyze_And_Resolve
(N
, Typ
);
4112 -- The only case that can get this far is the dynamic case of the old
4113 -- Ada 83 Mantissa attribute for the fixed-point case. For this case,
4120 -- ityp (System.Mantissa.Mantissa_Value
4121 -- (Integer'Integer_Value (typ'First),
4122 -- Integer'Integer_Value (typ'Last)));
4124 when Attribute_Mantissa
=> Mantissa
: begin
4127 Make_Function_Call
(Loc
,
4128 Name
=> New_Occurrence_Of
(RTE
(RE_Mantissa_Value
), Loc
),
4130 Parameter_Associations
=> New_List
(
4132 Make_Attribute_Reference
(Loc
,
4133 Prefix
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
4134 Attribute_Name
=> Name_Integer_Value
,
4135 Expressions
=> New_List
(
4137 Make_Attribute_Reference
(Loc
,
4138 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
4139 Attribute_Name
=> Name_First
))),
4141 Make_Attribute_Reference
(Loc
,
4142 Prefix
=> New_Occurrence_Of
(Standard_Integer
, Loc
),
4143 Attribute_Name
=> Name_Integer_Value
,
4144 Expressions
=> New_List
(
4146 Make_Attribute_Reference
(Loc
,
4147 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
4148 Attribute_Name
=> Name_Last
)))))));
4150 Analyze_And_Resolve
(N
, Typ
);
4157 when Attribute_Max
=>
4158 Expand_Min_Max_Attribute
(N
);
4160 ----------------------------------
4161 -- Max_Size_In_Storage_Elements --
4162 ----------------------------------
4164 when Attribute_Max_Size_In_Storage_Elements
=> declare
4165 Typ
: constant Entity_Id
:= Etype
(N
);
4168 Conversion_Added
: Boolean := False;
4169 -- A flag which tracks whether the original attribute has been
4170 -- wrapped inside a type conversion.
4173 Apply_Universal_Integer_Attribute_Checks
(N
);
4175 -- The universal integer check may sometimes add a type conversion,
4176 -- retrieve the original attribute reference from the expression.
4179 if Nkind
(Attr
) = N_Type_Conversion
then
4180 Attr
:= Expression
(Attr
);
4181 Conversion_Added
:= True;
4184 -- Heap-allocated controlled objects contain two extra pointers which
4185 -- are not part of the actual type. Transform the attribute reference
4186 -- into a runtime expression to add the size of the hidden header.
4188 -- Do not perform this expansion on .NET/JVM targets because the
4189 -- two pointers are already present in the type.
4191 if VM_Target
= No_VM
4192 and then Nkind
(Attr
) = N_Attribute_Reference
4193 and then Needs_Finalization
(Ptyp
)
4194 and then not Header_Size_Added
(Attr
)
4196 Set_Header_Size_Added
(Attr
);
4199 -- P'Max_Size_In_Storage_Elements +
4200 -- Universal_Integer
4201 -- (Header_Size_With_Padding (Ptyp'Alignment))
4205 Left_Opnd
=> Relocate_Node
(Attr
),
4207 Convert_To
(Universal_Integer
,
4208 Make_Function_Call
(Loc
,
4211 (RTE
(RE_Header_Size_With_Padding
), Loc
),
4213 Parameter_Associations
=> New_List
(
4214 Make_Attribute_Reference
(Loc
,
4216 New_Occurrence_Of
(Ptyp
, Loc
),
4217 Attribute_Name
=> Name_Alignment
))))));
4219 -- Add a conversion to the target type
4221 if not Conversion_Added
then
4223 Make_Type_Conversion
(Loc
,
4224 Subtype_Mark
=> New_Occurrence_Of
(Typ
, Loc
),
4225 Expression
=> Relocate_Node
(Attr
)));
4233 --------------------
4234 -- Mechanism_Code --
4235 --------------------
4237 when Attribute_Mechanism_Code
=>
4239 -- We must replace the prefix i the renamed case
4241 if Is_Entity_Name
(Pref
)
4242 and then Present
(Alias
(Entity
(Pref
)))
4244 Set_Renamed_Subprogram
(Pref
, Alias
(Entity
(Pref
)));
4251 when Attribute_Min
=>
4252 Expand_Min_Max_Attribute
(N
);
4258 when Attribute_Mod
=> Mod_Case
: declare
4259 Arg
: constant Node_Id
:= Relocate_Node
(First
(Exprs
));
4260 Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Arg
));
4261 Modv
: constant Uint
:= Modulus
(Btyp
);
4265 -- This is not so simple. The issue is what type to use for the
4266 -- computation of the modular value.
4268 -- The easy case is when the modulus value is within the bounds
4269 -- of the signed integer type of the argument. In this case we can
4270 -- just do the computation in that signed integer type, and then
4271 -- do an ordinary conversion to the target type.
4273 if Modv
<= Expr_Value
(Hi
) then
4278 Right_Opnd
=> Make_Integer_Literal
(Loc
, Modv
))));
4280 -- Here we know that the modulus is larger than type'Last of the
4281 -- integer type. There are two cases to consider:
4283 -- a) The integer value is non-negative. In this case, it is
4284 -- returned as the result (since it is less than the modulus).
4286 -- b) The integer value is negative. In this case, we know that the
4287 -- result is modulus + value, where the value might be as small as
4288 -- -modulus. The trouble is what type do we use to do the subtract.
4289 -- No type will do, since modulus can be as big as 2**64, and no
4290 -- integer type accommodates this value. Let's do bit of algebra
4293 -- = modulus - (-value)
4294 -- = (modulus - 1) - (-value - 1)
4296 -- Now modulus - 1 is certainly in range of the modular type.
4297 -- -value is in the range 1 .. modulus, so -value -1 is in the
4298 -- range 0 .. modulus-1 which is in range of the modular type.
4299 -- Furthermore, (-value - 1) can be expressed as -(value + 1)
4300 -- which we can compute using the integer base type.
4302 -- Once this is done we analyze the if expression without range
4303 -- checks, because we know everything is in range, and we want
4304 -- to prevent spurious warnings on either branch.
4308 Make_If_Expression
(Loc
,
4309 Expressions
=> New_List
(
4311 Left_Opnd
=> Duplicate_Subexpr
(Arg
),
4312 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
4315 Duplicate_Subexpr_No_Checks
(Arg
)),
4317 Make_Op_Subtract
(Loc
,
4319 Make_Integer_Literal
(Loc
,
4320 Intval
=> Modv
- 1),
4326 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Arg
),
4328 Make_Integer_Literal
(Loc
,
4329 Intval
=> 1))))))));
4333 Analyze_And_Resolve
(N
, Btyp
, Suppress
=> All_Checks
);
4340 -- Transforms 'Model into a call to the floating-point attribute
4341 -- function Model in Fat_xxx (where xxx is the root type).
4342 -- Expansion is avoided for cases the back end can handle directly.
4344 when Attribute_Model
=>
4345 if not Is_Inline_Floating_Point_Attribute
(N
) then
4346 Expand_Fpt_Attribute_R
(N
);
4353 -- The processing for Object_Size shares the processing for Size
4359 when Attribute_Old
=> Old
: declare
4365 Temp
:= Make_Temporary
(Loc
, 'T', Pref
);
4367 -- Set the entity kind now in order to mark the temporary as a
4368 -- handler of attribute 'Old's prefix.
4370 Set_Ekind
(Temp
, E_Constant
);
4371 Set_Stores_Attribute_Old_Prefix
(Temp
);
4373 -- Climb the parent chain looking for subprogram _Postconditions
4376 while Present
(Subp
) loop
4377 exit when Nkind
(Subp
) = N_Subprogram_Body
4378 and then Chars
(Defining_Entity
(Subp
)) = Name_uPostconditions
;
4380 -- If assertions are disabled, no need to create the declaration
4381 -- that preserves the value. The postcondition pragma in which
4382 -- 'Old appears will be checked or disabled according to the
4383 -- current policy in effect.
4385 if Nkind
(Subp
) = N_Pragma
and then not Is_Checked
(Subp
) then
4389 Subp
:= Parent
(Subp
);
4392 -- 'Old can only appear in a postcondition, the generated body of
4393 -- _Postconditions must be in the tree.
4395 pragma Assert
(Present
(Subp
));
4398 -- Temp : constant <Pref type> := <Pref>;
4401 Make_Object_Declaration
(Loc
,
4402 Defining_Identifier
=> Temp
,
4403 Constant_Present
=> True,
4404 Object_Definition
=> New_Occurrence_Of
(Etype
(N
), Loc
),
4405 Expression
=> Pref
);
4407 -- Push the scope of the related subprogram where _Postcondition
4408 -- resides as this ensures that the object will be analyzed in the
4411 Push_Scope
(Scope
(Defining_Entity
(Subp
)));
4413 -- The object declaration is inserted before the body of subprogram
4414 -- _Postconditions. This ensures that any precondition-like actions
4415 -- are still executed before any parameter values are captured and
4416 -- the multiple 'Old occurrences appear in order of declaration.
4418 Insert_Before_And_Analyze
(Subp
, Asn_Stm
);
4421 -- Ensure that the prefix of attribute 'Old is valid. The check must
4422 -- be inserted after the expansion of the attribute has taken place
4423 -- to reflect the new placement of the prefix.
4425 if Validity_Checks_On
and then Validity_Check_Operands
then
4426 Ensure_Valid
(Pref
);
4429 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
4432 ----------------------
4433 -- Overlaps_Storage --
4434 ----------------------
4436 when Attribute_Overlaps_Storage
=> Overlaps_Storage
: declare
4437 Loc
: constant Source_Ptr
:= Sloc
(N
);
4439 X
: constant Node_Id
:= Prefix
(N
);
4440 Y
: constant Node_Id
:= First
(Expressions
(N
));
4443 X_Addr
, Y_Addr
: Node_Id
;
4444 -- the expressions for their integer addresses
4446 X_Size
, Y_Size
: Node_Id
;
4447 -- the expressions for their sizes
4452 -- Attribute expands into:
4454 -- if X'Address < Y'address then
4455 -- (X'address + X'Size - 1) >= Y'address
4457 -- (Y'address + Y'size - 1) >= X'Address
4460 -- with the proper address operations. We convert addresses to
4461 -- integer addresses to use predefined arithmetic. The size is
4462 -- expressed in storage units.
4465 Unchecked_Convert_To
(RTE
(RE_Integer_Address
),
4466 Make_Attribute_Reference
(Loc
,
4467 Attribute_Name
=> Name_Address
,
4468 Prefix
=> New_Copy_Tree
(X
)));
4471 Unchecked_Convert_To
(RTE
(RE_Integer_Address
),
4472 Make_Attribute_Reference
(Loc
,
4473 Attribute_Name
=> Name_Address
,
4474 Prefix
=> New_Copy_Tree
(Y
)));
4477 Make_Op_Divide
(Loc
,
4479 Make_Attribute_Reference
(Loc
,
4480 Attribute_Name
=> Name_Size
,
4481 Prefix
=> New_Copy_Tree
(X
)),
4483 Make_Integer_Literal
(Loc
, System_Storage_Unit
));
4486 Make_Op_Divide
(Loc
,
4488 Make_Attribute_Reference
(Loc
,
4489 Attribute_Name
=> Name_Size
,
4490 Prefix
=> New_Copy_Tree
(Y
)),
4492 Make_Integer_Literal
(Loc
, System_Storage_Unit
));
4496 Left_Opnd
=> X_Addr
,
4497 Right_Opnd
=> Y_Addr
);
4500 Make_If_Expression
(Loc
,
4507 Left_Opnd
=> X_Addr
,
4509 Make_Op_Subtract
(Loc
,
4510 Left_Opnd
=> X_Size
,
4511 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))),
4512 Right_Opnd
=> Y_Addr
),
4516 Left_Opnd
=> Y_Addr
,
4518 Make_Op_Subtract
(Loc
,
4519 Left_Opnd
=> Y_Size
,
4520 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1))),
4521 Right_Opnd
=> X_Addr
))));
4523 Analyze_And_Resolve
(N
, Standard_Boolean
);
4524 end Overlaps_Storage
;
4530 when Attribute_Output
=> Output
: declare
4531 P_Type
: constant Entity_Id
:= Entity
(Pref
);
4532 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
4540 -- If no underlying type, we have an error that will be diagnosed
4541 -- elsewhere, so here we just completely ignore the expansion.
4547 -- Stream operations can appear in user code even if the restriction
4548 -- No_Streams is active (for example, when instantiating a predefined
4549 -- container). In that case rewrite the attribute as a Raise to
4550 -- prevent any run-time use.
4552 if Restriction_Active
(No_Streams
) then
4554 Make_Raise_Program_Error
(Sloc
(N
),
4555 Reason
=> PE_Stream_Operation_Not_Allowed
));
4556 Set_Etype
(N
, Standard_Void_Type
);
4560 -- If TSS for Output is present, just call it
4562 Pname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Output
);
4564 if Present
(Pname
) then
4568 -- If there is a Stream_Convert pragma, use it, we rewrite
4570 -- sourcetyp'Output (stream, Item)
4574 -- strmtyp'Output (Stream, strmwrite (acttyp (Item)));
4576 -- where strmwrite is the given Write function that converts an
4577 -- argument of type sourcetyp or a type acctyp, from which it is
4578 -- derived to type strmtyp. The conversion to acttyp is required
4579 -- for the derived case.
4581 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
4583 if Present
(Prag
) then
4585 Next
(Next
(First
(Pragma_Argument_Associations
(Prag
))));
4586 Wfunc
:= Entity
(Expression
(Arg3
));
4589 Make_Attribute_Reference
(Loc
,
4590 Prefix
=> New_Occurrence_Of
(Etype
(Wfunc
), Loc
),
4591 Attribute_Name
=> Name_Output
,
4592 Expressions
=> New_List
(
4593 Relocate_Node
(First
(Exprs
)),
4594 Make_Function_Call
(Loc
,
4595 Name
=> New_Occurrence_Of
(Wfunc
, Loc
),
4596 Parameter_Associations
=> New_List
(
4597 OK_Convert_To
(Etype
(First_Formal
(Wfunc
)),
4598 Relocate_Node
(Next
(First
(Exprs
)))))))));
4603 -- For elementary types, we call the W_xxx routine directly. Note
4604 -- that the effect of Write and Output is identical for the case
4605 -- of an elementary type (there are no discriminants or bounds).
4607 elsif Is_Elementary_Type
(U_Type
) then
4609 -- A special case arises if we have a defined _Write routine,
4610 -- since in this case we are required to call this routine.
4612 if Present
(TSS
(Base_Type
(U_Type
), TSS_Stream_Write
)) then
4613 Build_Record_Or_Elementary_Output_Procedure
4614 (Loc
, U_Type
, Decl
, Pname
);
4615 Insert_Action
(N
, Decl
);
4617 -- For normal cases, we call the W_xxx routine directly
4620 Rewrite
(N
, Build_Elementary_Write_Call
(N
));
4627 elsif Is_Array_Type
(U_Type
) then
4628 Build_Array_Output_Procedure
(Loc
, U_Type
, Decl
, Pname
);
4629 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
4631 -- Class-wide case, first output external tag, then dispatch
4632 -- to the appropriate primitive Output function (RM 13.13.2(31)).
4634 elsif Is_Class_Wide_Type
(P_Type
) then
4636 -- No need to do anything else compiling under restriction
4637 -- No_Dispatching_Calls. During the semantic analysis we
4638 -- already notified such violation.
4640 if Restriction_Active
(No_Dispatching_Calls
) then
4645 Strm
: constant Node_Id
:= First
(Exprs
);
4646 Item
: constant Node_Id
:= Next
(Strm
);
4649 -- Ada 2005 (AI-344): Check that the accessibility level
4650 -- of the type of the output object is not deeper than
4651 -- that of the attribute's prefix type.
4653 -- if Get_Access_Level (Item'Tag)
4654 -- /= Get_Access_Level (P_Type'Tag)
4659 -- String'Output (Strm, External_Tag (Item'Tag));
4661 -- We cannot figure out a practical way to implement this
4662 -- accessibility check on virtual machines, so we omit it.
4664 if Ada_Version
>= Ada_2005
4665 and then Tagged_Type_Expansion
4668 Make_Implicit_If_Statement
(N
,
4672 Build_Get_Access_Level
(Loc
,
4673 Make_Attribute_Reference
(Loc
,
4676 Duplicate_Subexpr
(Item
,
4678 Attribute_Name
=> Name_Tag
)),
4681 Make_Integer_Literal
(Loc
,
4682 Type_Access_Level
(P_Type
))),
4685 New_List
(Make_Raise_Statement
(Loc
,
4687 RTE
(RE_Tag_Error
), Loc
)))));
4691 Make_Attribute_Reference
(Loc
,
4692 Prefix
=> New_Occurrence_Of
(Standard_String
, Loc
),
4693 Attribute_Name
=> Name_Output
,
4694 Expressions
=> New_List
(
4695 Relocate_Node
(Duplicate_Subexpr
(Strm
)),
4696 Make_Function_Call
(Loc
,
4698 New_Occurrence_Of
(RTE
(RE_External_Tag
), Loc
),
4699 Parameter_Associations
=> New_List
(
4700 Make_Attribute_Reference
(Loc
,
4703 (Duplicate_Subexpr
(Item
, Name_Req
=> True)),
4704 Attribute_Name
=> Name_Tag
))))));
4707 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Output
);
4709 -- Tagged type case, use the primitive Output function
4711 elsif Is_Tagged_Type
(U_Type
) then
4712 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Output
);
4714 -- All other record type cases, including protected records.
4715 -- The latter only arise for expander generated code for
4716 -- handling shared passive partition access.
4720 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
4722 -- Ada 2005 (AI-216): Program_Error is raised when executing
4723 -- the default implementation of the Output attribute of an
4724 -- unchecked union type if the type lacks default discriminant
4727 if Is_Unchecked_Union
(Base_Type
(U_Type
))
4728 and then No
(Discriminant_Constraint
(U_Type
))
4731 Make_Raise_Program_Error
(Loc
,
4732 Reason
=> PE_Unchecked_Union_Restriction
));
4737 Build_Record_Or_Elementary_Output_Procedure
4738 (Loc
, Base_Type
(U_Type
), Decl
, Pname
);
4739 Insert_Action
(N
, Decl
);
4743 -- If we fall through, Pname is the name of the procedure to call
4745 Rewrite_Stream_Proc_Call
(Pname
);
4752 -- For enumeration types with a standard representation, Pos is
4753 -- handled by the back end.
4755 -- For enumeration types, with a non-standard representation we generate
4756 -- a call to the _Rep_To_Pos function created when the type was frozen.
4757 -- The call has the form
4759 -- _rep_to_pos (expr, flag)
4761 -- The parameter flag is True if range checks are enabled, causing
4762 -- Program_Error to be raised if the expression has an invalid
4763 -- representation, and False if range checks are suppressed.
4765 -- For integer types, Pos is equivalent to a simple integer
4766 -- conversion and we rewrite it as such
4768 when Attribute_Pos
=> Pos
:
4770 Etyp
: Entity_Id
:= Base_Type
(Entity
(Pref
));
4773 -- Deal with zero/non-zero boolean values
4775 if Is_Boolean_Type
(Etyp
) then
4776 Adjust_Condition
(First
(Exprs
));
4777 Etyp
:= Standard_Boolean
;
4778 Set_Prefix
(N
, New_Occurrence_Of
(Standard_Boolean
, Loc
));
4781 -- Case of enumeration type
4783 if Is_Enumeration_Type
(Etyp
) then
4785 -- Non-standard enumeration type (generate call)
4787 if Present
(Enum_Pos_To_Rep
(Etyp
)) then
4788 Append_To
(Exprs
, Rep_To_Pos_Flag
(Etyp
, Loc
));
4791 Make_Function_Call
(Loc
,
4793 New_Occurrence_Of
(TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
4794 Parameter_Associations
=> Exprs
)));
4796 Analyze_And_Resolve
(N
, Typ
);
4798 -- Standard enumeration type (do universal integer check)
4801 Apply_Universal_Integer_Attribute_Checks
(N
);
4804 -- Deal with integer types (replace by conversion)
4806 elsif Is_Integer_Type
(Etyp
) then
4807 Rewrite
(N
, Convert_To
(Typ
, First
(Exprs
)));
4808 Analyze_And_Resolve
(N
, Typ
);
4817 -- We compute this if a component clause was present, otherwise we leave
4818 -- the computation up to the back end, since we don't know what layout
4821 when Attribute_Position
=> Position_Attr
:
4823 CE
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
4826 if Present
(Component_Clause
(CE
)) then
4828 -- In Ada 2005 (or later) if we have the non-default bit order,
4829 -- then we return the original value as given in the component
4830 -- clause (RM 2005 13.5.2(2/2)).
4832 if Ada_Version
>= Ada_2005
4833 and then Reverse_Bit_Order
(Scope
(CE
))
4836 Make_Integer_Literal
(Loc
,
4837 Intval
=> Expr_Value
(Position
(Component_Clause
(CE
)))));
4839 -- Otherwise (Ada 83 or 95, or default bit order specified in
4840 -- later Ada version), return the normalized value.
4844 Make_Integer_Literal
(Loc
,
4845 Intval
=> Component_Bit_Offset
(CE
) / System_Storage_Unit
));
4848 Analyze_And_Resolve
(N
, Typ
);
4850 -- If back end is doing things, just apply universal integer checks
4853 Apply_Universal_Integer_Attribute_Checks
(N
);
4861 -- 1. Deal with enumeration types with holes
4862 -- 2. For floating-point, generate call to attribute function and deal
4863 -- with range checking if Check_Float_Overflow mode is set.
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).
4937 elsif Is_Floating_Point_Type
(Ptyp
) then
4939 -- Handle case of range check. The Do_Range_Check flag is set only
4940 -- in Check_Float_Overflow mode, and what we need is a specific
4941 -- check against typ'First, since that is the only overflow case.
4944 Expr
: constant Node_Id
:= First
(Exprs
);
4946 if Do_Range_Check
(Expr
) then
4947 Set_Do_Range_Check
(Expr
, False);
4949 Make_Raise_Constraint_Error
(Loc
,
4952 Left_Opnd
=> Duplicate_Subexpr
(Expr
),
4954 Make_Attribute_Reference
(Loc
,
4955 Attribute_Name
=> Name_First
,
4957 New_Occurrence_Of
(Base_Type
(Ptyp
), Loc
))),
4958 Reason
=> CE_Overflow_Check_Failed
),
4959 Suppress
=> All_Checks
);
4963 -- Transform into call to attribute function
4965 Expand_Fpt_Attribute_R
(N
);
4966 Analyze_And_Resolve
(N
, Typ
);
4968 -- For modular types, nothing to do (no overflow, since wraps)
4970 elsif Is_Modular_Integer_Type
(Ptyp
) then
4973 -- For other types, if argument is marked as needing a range check or
4974 -- overflow checking is enabled, we must generate a check.
4976 elsif not Overflow_Checks_Suppressed
(Ptyp
)
4977 or else Do_Range_Check
(First
(Exprs
))
4979 Set_Do_Range_Check
(First
(Exprs
), False);
4980 Expand_Pred_Succ_Attribute
(N
);
4988 -- Ada 2005 (AI-327): Dynamic ceiling priorities
4990 -- We rewrite X'Priority as the following run-time call:
4992 -- Get_Ceiling (X._Object)
4994 -- Note that although X'Priority is notionally an object, it is quite
4995 -- deliberately not defined as an aliased object in the RM. This means
4996 -- that it works fine to rewrite it as a call, without having to worry
4997 -- about complications that would other arise from X'Priority'Access,
4998 -- which is illegal, because of the lack of aliasing.
5000 when Attribute_Priority
=>
5003 Conctyp
: Entity_Id
;
5004 Object_Parm
: Node_Id
;
5006 RT_Subprg_Name
: Node_Id
;
5009 -- Look for the enclosing concurrent type
5011 Conctyp
:= Current_Scope
;
5012 while not Is_Concurrent_Type
(Conctyp
) loop
5013 Conctyp
:= Scope
(Conctyp
);
5016 pragma Assert
(Is_Protected_Type
(Conctyp
));
5018 -- Generate the actual of the call
5020 Subprg
:= Current_Scope
;
5021 while not Present
(Protected_Body_Subprogram
(Subprg
)) loop
5022 Subprg
:= Scope
(Subprg
);
5025 -- Use of 'Priority inside protected entries and barriers (in
5026 -- both cases the type of the first formal of their expanded
5027 -- subprogram is Address)
5029 if Etype
(First_Entity
(Protected_Body_Subprogram
(Subprg
)))
5033 New_Itype
: Entity_Id
;
5036 -- In the expansion of protected entries the type of the
5037 -- first formal of the Protected_Body_Subprogram is an
5038 -- Address. In order to reference the _object component
5041 -- type T is access p__ptTV;
5044 New_Itype
:= Create_Itype
(E_Access_Type
, N
);
5045 Set_Etype
(New_Itype
, New_Itype
);
5046 Set_Directly_Designated_Type
(New_Itype
,
5047 Corresponding_Record_Type
(Conctyp
));
5048 Freeze_Itype
(New_Itype
, N
);
5051 -- T!(O)._object'unchecked_access
5054 Make_Attribute_Reference
(Loc
,
5056 Make_Selected_Component
(Loc
,
5058 Unchecked_Convert_To
(New_Itype
,
5061 (Protected_Body_Subprogram
(Subprg
)),
5064 Make_Identifier
(Loc
, Name_uObject
)),
5065 Attribute_Name
=> Name_Unchecked_Access
);
5068 -- Use of 'Priority inside a protected subprogram
5072 Make_Attribute_Reference
(Loc
,
5074 Make_Selected_Component
(Loc
,
5075 Prefix
=> New_Occurrence_Of
5077 (Protected_Body_Subprogram
(Subprg
)),
5079 Selector_Name
=> Make_Identifier
(Loc
, Name_uObject
)),
5080 Attribute_Name
=> Name_Unchecked_Access
);
5083 -- Select the appropriate run-time subprogram
5085 if Number_Entries
(Conctyp
) = 0 then
5087 New_Occurrence_Of
(RTE
(RE_Get_Ceiling
), Loc
);
5090 New_Occurrence_Of
(RTE
(RO_PE_Get_Ceiling
), Loc
);
5094 Make_Function_Call
(Loc
,
5095 Name
=> RT_Subprg_Name
,
5096 Parameter_Associations
=> New_List
(Object_Parm
));
5100 -- Avoid the generation of extra checks on the pointer to the
5101 -- protected object.
5103 Analyze_And_Resolve
(N
, Typ
, Suppress
=> Access_Check
);
5110 when Attribute_Range_Length
=> Range_Length
: begin
5112 -- The only special processing required is for the case where
5113 -- Range_Length is applied to an enumeration type with holes.
5114 -- In this case we transform
5120 -- X'Pos (X'Last) - X'Pos (X'First) + 1
5122 -- So that the result reflects the proper Pos values instead
5123 -- of the underlying representations.
5125 if Is_Enumeration_Type
(Ptyp
)
5126 and then Has_Non_Standard_Rep
(Ptyp
)
5131 Make_Op_Subtract
(Loc
,
5133 Make_Attribute_Reference
(Loc
,
5134 Attribute_Name
=> Name_Pos
,
5135 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
5136 Expressions
=> New_List
(
5137 Make_Attribute_Reference
(Loc
,
5138 Attribute_Name
=> Name_Last
,
5139 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
)))),
5142 Make_Attribute_Reference
(Loc
,
5143 Attribute_Name
=> Name_Pos
,
5144 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
5145 Expressions
=> New_List
(
5146 Make_Attribute_Reference
(Loc
,
5147 Attribute_Name
=> Name_First
,
5148 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
))))),
5150 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)));
5152 Analyze_And_Resolve
(N
, Typ
);
5154 -- For all other cases, the attribute is handled by the back end, but
5155 -- we need to deal with the case of the range check on a universal
5159 Apply_Universal_Integer_Attribute_Checks
(N
);
5167 when Attribute_Read
=> Read
: declare
5168 P_Type
: constant Entity_Id
:= Entity
(Pref
);
5169 B_Type
: constant Entity_Id
:= Base_Type
(P_Type
);
5170 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
5180 -- If no underlying type, we have an error that will be diagnosed
5181 -- elsewhere, so here we just completely ignore the expansion.
5187 -- Stream operations can appear in user code even if the restriction
5188 -- No_Streams is active (for example, when instantiating a predefined
5189 -- container). In that case rewrite the attribute as a Raise to
5190 -- prevent any run-time use.
5192 if Restriction_Active
(No_Streams
) then
5194 Make_Raise_Program_Error
(Sloc
(N
),
5195 Reason
=> PE_Stream_Operation_Not_Allowed
));
5196 Set_Etype
(N
, B_Type
);
5200 -- The simple case, if there is a TSS for Read, just call it
5202 Pname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Read
);
5204 if Present
(Pname
) then
5208 -- If there is a Stream_Convert pragma, use it, we rewrite
5210 -- sourcetyp'Read (stream, Item)
5214 -- Item := sourcetyp (strmread (strmtyp'Input (Stream)));
5216 -- where strmread is the given Read function that converts an
5217 -- argument of type strmtyp to type sourcetyp or a type from which
5218 -- it is derived. The conversion to sourcetyp is required in the
5221 -- A special case arises if Item is a type conversion in which
5222 -- case, we have to expand to:
5224 -- Itemx := typex (strmread (strmtyp'Input (Stream)));
5226 -- where Itemx is the expression of the type conversion (i.e.
5227 -- the actual object), and typex is the type of Itemx.
5229 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
5231 if Present
(Prag
) then
5232 Arg2
:= Next
(First
(Pragma_Argument_Associations
(Prag
)));
5233 Rfunc
:= Entity
(Expression
(Arg2
));
5234 Lhs
:= Relocate_Node
(Next
(First
(Exprs
)));
5236 OK_Convert_To
(B_Type
,
5237 Make_Function_Call
(Loc
,
5238 Name
=> New_Occurrence_Of
(Rfunc
, Loc
),
5239 Parameter_Associations
=> New_List
(
5240 Make_Attribute_Reference
(Loc
,
5243 (Etype
(First_Formal
(Rfunc
)), Loc
),
5244 Attribute_Name
=> Name_Input
,
5245 Expressions
=> New_List
(
5246 Relocate_Node
(First
(Exprs
)))))));
5248 if Nkind
(Lhs
) = N_Type_Conversion
then
5249 Lhs
:= Expression
(Lhs
);
5250 Rhs
:= Convert_To
(Etype
(Lhs
), Rhs
);
5254 Make_Assignment_Statement
(Loc
,
5256 Expression
=> Rhs
));
5257 Set_Assignment_OK
(Lhs
);
5261 -- For elementary types, we call the I_xxx routine using the first
5262 -- parameter and then assign the result into the second parameter.
5263 -- We set Assignment_OK to deal with the conversion case.
5265 elsif Is_Elementary_Type
(U_Type
) then
5271 Lhs
:= Relocate_Node
(Next
(First
(Exprs
)));
5272 Rhs
:= Build_Elementary_Input_Call
(N
);
5274 if Nkind
(Lhs
) = N_Type_Conversion
then
5275 Lhs
:= Expression
(Lhs
);
5276 Rhs
:= Convert_To
(Etype
(Lhs
), Rhs
);
5279 Set_Assignment_OK
(Lhs
);
5282 Make_Assignment_Statement
(Loc
,
5284 Expression
=> Rhs
));
5292 elsif Is_Array_Type
(U_Type
) then
5293 Build_Array_Read_Procedure
(N
, U_Type
, Decl
, Pname
);
5294 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
5296 -- Tagged type case, use the primitive Read function. Note that
5297 -- this will dispatch in the class-wide case which is what we want
5299 elsif Is_Tagged_Type
(U_Type
) then
5300 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Read
);
5302 -- All other record type cases, including protected records. The
5303 -- latter only arise for expander generated code for handling
5304 -- shared passive partition access.
5308 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
5310 -- Ada 2005 (AI-216): Program_Error is raised when executing
5311 -- the default implementation of the Read attribute of an
5312 -- Unchecked_Union type.
5314 if Is_Unchecked_Union
(Base_Type
(U_Type
)) then
5316 Make_Raise_Program_Error
(Loc
,
5317 Reason
=> PE_Unchecked_Union_Restriction
));
5320 if Has_Discriminants
(U_Type
)
5322 (Discriminant_Default_Value
(First_Discriminant
(U_Type
)))
5324 Build_Mutable_Record_Read_Procedure
5325 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
5327 Build_Record_Read_Procedure
5328 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
5331 -- Suppress checks, uninitialized or otherwise invalid
5332 -- data does not cause constraint errors to be raised for
5333 -- a complete record read.
5335 Insert_Action
(N
, Decl
, All_Checks
);
5339 Rewrite_Stream_Proc_Call
(Pname
);
5346 -- Ref is identical to To_Address, see To_Address for processing
5352 -- Transforms 'Remainder into a call to the floating-point attribute
5353 -- function Remainder in Fat_xxx (where xxx is the root type)
5355 when Attribute_Remainder
=>
5356 Expand_Fpt_Attribute_RR
(N
);
5362 -- Transform 'Result into reference to _Result formal. At the point
5363 -- where a legal 'Result attribute is expanded, we know that we are in
5364 -- the context of a _Postcondition function with a _Result parameter.
5366 when Attribute_Result
=>
5367 Rewrite
(N
, Make_Identifier
(Loc
, Chars
=> Name_uResult
));
5368 Analyze_And_Resolve
(N
, Typ
);
5374 -- The handling of the Round attribute is quite delicate. The processing
5375 -- in Sem_Attr introduced a conversion to universal real, reflecting the
5376 -- semantics of Round, but we do not want anything to do with universal
5377 -- real at runtime, since this corresponds to using floating-point
5380 -- What we have now is that the Etype of the Round attribute correctly
5381 -- indicates the final result type. The operand of the Round is the
5382 -- conversion to universal real, described above, and the operand of
5383 -- this conversion is the actual operand of Round, which may be the
5384 -- special case of a fixed point multiplication or division (Etype =
5387 -- The exapander will expand first the operand of the conversion, then
5388 -- the conversion, and finally the round attribute itself, since we
5389 -- always work inside out. But we cannot simply process naively in this
5390 -- order. In the semantic world where universal fixed and real really
5391 -- exist and have infinite precision, there is no problem, but in the
5392 -- implementation world, where universal real is a floating-point type,
5393 -- we would get the wrong result.
5395 -- So the approach is as follows. First, when expanding a multiply or
5396 -- divide whose type is universal fixed, we do nothing at all, instead
5397 -- deferring the operation till later.
5399 -- The actual processing is done in Expand_N_Type_Conversion which
5400 -- handles the special case of Round by looking at its parent to see if
5401 -- it is a Round attribute, and if it is, handling the conversion (or
5402 -- its fixed multiply/divide child) in an appropriate manner.
5404 -- This means that by the time we get to expanding the Round attribute
5405 -- itself, the Round is nothing more than a type conversion (and will
5406 -- often be a null type conversion), so we just replace it with the
5407 -- appropriate conversion operation.
5409 when Attribute_Round
=>
5411 Convert_To
(Etype
(N
), Relocate_Node
(First
(Exprs
))));
5412 Analyze_And_Resolve
(N
);
5418 -- Transforms 'Rounding into a call to the floating-point attribute
5419 -- function Rounding in Fat_xxx (where xxx is the root type)
5420 -- Expansion is avoided for cases the back end can handle directly.
5422 when Attribute_Rounding
=>
5423 if not Is_Inline_Floating_Point_Attribute
(N
) then
5424 Expand_Fpt_Attribute_R
(N
);
5431 -- Transforms 'Scaling into a call to the floating-point attribute
5432 -- function Scaling in Fat_xxx (where xxx is the root type)
5434 when Attribute_Scaling
=>
5435 Expand_Fpt_Attribute_RI
(N
);
5437 -------------------------
5438 -- Simple_Storage_Pool --
5439 -------------------------
5441 when Attribute_Simple_Storage_Pool
=>
5443 Make_Type_Conversion
(Loc
,
5444 Subtype_Mark
=> New_Occurrence_Of
(Etype
(N
), Loc
),
5445 Expression
=> New_Occurrence_Of
(Entity
(N
), Loc
)));
5446 Analyze_And_Resolve
(N
, Typ
);
5452 when Attribute_Size |
5453 Attribute_Object_Size |
5454 Attribute_Value_Size |
5455 Attribute_VADS_Size
=> Size
:
5462 -- Processing for VADS_Size case. Note that this processing removes
5463 -- all traces of VADS_Size from the tree, and completes all required
5464 -- processing for VADS_Size by translating the attribute reference
5465 -- to an appropriate Size or Object_Size reference.
5467 if Id
= Attribute_VADS_Size
5468 or else (Use_VADS_Size
and then Id
= Attribute_Size
)
5470 -- If the size is specified, then we simply use the specified
5471 -- size. This applies to both types and objects. The size of an
5472 -- object can be specified in the following ways:
5474 -- An explicit size object is given for an object
5475 -- A component size is specified for an indexed component
5476 -- A component clause is specified for a selected component
5477 -- The object is a component of a packed composite object
5479 -- If the size is specified, then VADS_Size of an object
5481 if (Is_Entity_Name
(Pref
)
5482 and then Present
(Size_Clause
(Entity
(Pref
))))
5484 (Nkind
(Pref
) = N_Component_Clause
5485 and then (Present
(Component_Clause
5486 (Entity
(Selector_Name
(Pref
))))
5487 or else Is_Packed
(Etype
(Prefix
(Pref
)))))
5489 (Nkind
(Pref
) = N_Indexed_Component
5490 and then (Component_Size
(Etype
(Prefix
(Pref
))) /= 0
5491 or else Is_Packed
(Etype
(Prefix
(Pref
)))))
5493 Set_Attribute_Name
(N
, Name_Size
);
5495 -- Otherwise if we have an object rather than a type, then the
5496 -- VADS_Size attribute applies to the type of the object, rather
5497 -- than the object itself. This is one of the respects in which
5498 -- VADS_Size differs from Size.
5501 if (not Is_Entity_Name
(Pref
)
5502 or else not Is_Type
(Entity
(Pref
)))
5503 and then (Is_Scalar_Type
(Ptyp
) or else Is_Constrained
(Ptyp
))
5505 Rewrite
(Pref
, New_Occurrence_Of
(Ptyp
, Loc
));
5508 -- For a scalar type for which no size was explicitly given,
5509 -- VADS_Size means Object_Size. This is the other respect in
5510 -- which VADS_Size differs from Size.
5512 if Is_Scalar_Type
(Ptyp
) and then No
(Size_Clause
(Ptyp
)) then
5513 Set_Attribute_Name
(N
, Name_Object_Size
);
5515 -- In all other cases, Size and VADS_Size are the sane
5518 Set_Attribute_Name
(N
, Name_Size
);
5523 -- For class-wide types, X'Class'Size is transformed into a direct
5524 -- reference to the Size of the class type, so that the back end does
5525 -- not have to deal with the X'Class'Size reference.
5527 if Is_Entity_Name
(Pref
)
5528 and then Is_Class_Wide_Type
(Entity
(Pref
))
5530 Rewrite
(Prefix
(N
), New_Occurrence_Of
(Entity
(Pref
), Loc
));
5533 -- For X'Size applied to an object of a class-wide type, transform
5534 -- X'Size into a call to the primitive operation _Size applied to X.
5536 elsif Is_Class_Wide_Type
(Ptyp
)
5537 or else (Id
= Attribute_Size
5538 and then Is_Tagged_Type
(Ptyp
)
5539 and then Has_Unknown_Discriminants
(Ptyp
))
5541 -- No need to do anything else compiling under restriction
5542 -- No_Dispatching_Calls. During the semantic analysis we
5543 -- already notified such violation.
5545 if Restriction_Active
(No_Dispatching_Calls
) then
5550 Make_Function_Call
(Loc
,
5551 Name
=> New_Occurrence_Of
5552 (Find_Prim_Op
(Ptyp
, Name_uSize
), Loc
),
5553 Parameter_Associations
=> New_List
(Pref
));
5555 if Typ
/= Standard_Long_Long_Integer
then
5557 -- The context is a specific integer type with which the
5558 -- original attribute was compatible. The function has a
5559 -- specific type as well, so to preserve the compatibility
5560 -- we must convert explicitly.
5562 New_Node
:= Convert_To
(Typ
, New_Node
);
5565 Rewrite
(N
, New_Node
);
5566 Analyze_And_Resolve
(N
, Typ
);
5569 -- Case of known RM_Size of a type
5571 elsif (Id
= Attribute_Size
or else Id
= Attribute_Value_Size
)
5572 and then Is_Entity_Name
(Pref
)
5573 and then Is_Type
(Entity
(Pref
))
5574 and then Known_Static_RM_Size
(Entity
(Pref
))
5576 Siz
:= RM_Size
(Entity
(Pref
));
5578 -- Case of known Esize of a type
5580 elsif Id
= Attribute_Object_Size
5581 and then Is_Entity_Name
(Pref
)
5582 and then Is_Type
(Entity
(Pref
))
5583 and then Known_Static_Esize
(Entity
(Pref
))
5585 Siz
:= Esize
(Entity
(Pref
));
5587 -- Case of known size of object
5589 elsif Id
= Attribute_Size
5590 and then Is_Entity_Name
(Pref
)
5591 and then Is_Object
(Entity
(Pref
))
5592 and then Known_Esize
(Entity
(Pref
))
5593 and then Known_Static_Esize
(Entity
(Pref
))
5595 Siz
:= Esize
(Entity
(Pref
));
5597 -- For an array component, we can do Size in the front end
5598 -- if the component_size of the array is set.
5600 elsif Nkind
(Pref
) = N_Indexed_Component
then
5601 Siz
:= Component_Size
(Etype
(Prefix
(Pref
)));
5603 -- For a record component, we can do Size in the front end if there
5604 -- is a component clause, or if the record is packed and the
5605 -- component's size is known at compile time.
5607 elsif Nkind
(Pref
) = N_Selected_Component
then
5609 Rec
: constant Entity_Id
:= Etype
(Prefix
(Pref
));
5610 Comp
: constant Entity_Id
:= Entity
(Selector_Name
(Pref
));
5613 if Present
(Component_Clause
(Comp
)) then
5614 Siz
:= Esize
(Comp
);
5616 elsif Is_Packed
(Rec
) then
5617 Siz
:= RM_Size
(Ptyp
);
5620 Apply_Universal_Integer_Attribute_Checks
(N
);
5625 -- All other cases are handled by the back end
5628 Apply_Universal_Integer_Attribute_Checks
(N
);
5630 -- If Size is applied to a formal parameter that is of a packed
5631 -- array subtype, then apply Size to the actual subtype.
5633 if Is_Entity_Name
(Pref
)
5634 and then Is_Formal
(Entity
(Pref
))
5635 and then Is_Array_Type
(Ptyp
)
5636 and then Is_Packed
(Ptyp
)
5639 Make_Attribute_Reference
(Loc
,
5641 New_Occurrence_Of
(Get_Actual_Subtype
(Pref
), Loc
),
5642 Attribute_Name
=> Name_Size
));
5643 Analyze_And_Resolve
(N
, Typ
);
5646 -- If Size applies to a dereference of an access to unconstrained
5647 -- packed array, the back end needs to see its unconstrained
5648 -- nominal type, but also a hint to the actual constrained type.
5650 if Nkind
(Pref
) = N_Explicit_Dereference
5651 and then Is_Array_Type
(Ptyp
)
5652 and then not Is_Constrained
(Ptyp
)
5653 and then Is_Packed
(Ptyp
)
5655 Set_Actual_Designated_Subtype
(Pref
,
5656 Get_Actual_Subtype
(Pref
));
5662 -- Common processing for record and array component case
5664 if Siz
/= No_Uint
and then Siz
/= 0 then
5666 CS
: constant Boolean := Comes_From_Source
(N
);
5669 Rewrite
(N
, Make_Integer_Literal
(Loc
, Siz
));
5671 -- This integer literal is not a static expression. We do not
5672 -- call Analyze_And_Resolve here, because this would activate
5673 -- the circuit for deciding that a static value was out of
5674 -- range, and we don't want that.
5676 -- So just manually set the type, mark the expression as non-
5677 -- static, and then ensure that the result is checked properly
5678 -- if the attribute comes from source (if it was internally
5679 -- generated, we never need a constraint check).
5682 Set_Is_Static_Expression
(N
, False);
5685 Apply_Constraint_Check
(N
, Typ
);
5695 when Attribute_Storage_Pool
=>
5697 Make_Type_Conversion
(Loc
,
5698 Subtype_Mark
=> New_Occurrence_Of
(Etype
(N
), Loc
),
5699 Expression
=> New_Occurrence_Of
(Entity
(N
), Loc
)));
5700 Analyze_And_Resolve
(N
, Typ
);
5706 when Attribute_Storage_Size
=> Storage_Size
: declare
5707 Alloc_Op
: Entity_Id
:= Empty
;
5711 -- Access type case, always go to the root type
5713 -- The case of access types results in a value of zero for the case
5714 -- where no storage size attribute clause has been given. If a
5715 -- storage size has been given, then the attribute is converted
5716 -- to a reference to the variable used to hold this value.
5718 if Is_Access_Type
(Ptyp
) then
5719 if Present
(Storage_Size_Variable
(Root_Type
(Ptyp
))) then
5721 Make_Attribute_Reference
(Loc
,
5722 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
5723 Attribute_Name
=> Name_Max
,
5724 Expressions
=> New_List
(
5725 Make_Integer_Literal
(Loc
, 0),
5728 (Storage_Size_Variable
(Root_Type
(Ptyp
)), Loc
)))));
5730 elsif Present
(Associated_Storage_Pool
(Root_Type
(Ptyp
))) then
5732 -- If the access type is associated with a simple storage pool
5733 -- object, then attempt to locate the optional Storage_Size
5734 -- function of the simple storage pool type. If not found,
5735 -- then the result will default to zero.
5737 if Present
(Get_Rep_Pragma
(Root_Type
(Ptyp
),
5738 Name_Simple_Storage_Pool_Type
))
5741 Pool_Type
: constant Entity_Id
:=
5742 Base_Type
(Etype
(Entity
(N
)));
5745 Alloc_Op
:= Get_Name_Entity_Id
(Name_Storage_Size
);
5746 while Present
(Alloc_Op
) loop
5747 if Scope
(Alloc_Op
) = Scope
(Pool_Type
)
5748 and then Present
(First_Formal
(Alloc_Op
))
5749 and then Etype
(First_Formal
(Alloc_Op
)) = Pool_Type
5754 Alloc_Op
:= Homonym
(Alloc_Op
);
5758 -- In the normal Storage_Pool case, retrieve the primitive
5759 -- function associated with the pool type.
5764 (Etype
(Associated_Storage_Pool
(Root_Type
(Ptyp
))),
5765 Attribute_Name
(N
));
5768 -- If Storage_Size wasn't found (can only occur in the simple
5769 -- storage pool case), then simply use zero for the result.
5771 if not Present
(Alloc_Op
) then
5772 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
5774 -- Otherwise, rewrite the allocator as a call to pool type's
5775 -- Storage_Size function.
5780 Make_Function_Call
(Loc
,
5782 New_Occurrence_Of
(Alloc_Op
, Loc
),
5784 Parameter_Associations
=> New_List
(
5786 (Associated_Storage_Pool
5787 (Root_Type
(Ptyp
)), Loc
)))));
5791 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
5794 Analyze_And_Resolve
(N
, Typ
);
5796 -- For tasks, we retrieve the size directly from the TCB. The
5797 -- size may depend on a discriminant of the type, and therefore
5798 -- can be a per-object expression, so type-level information is
5799 -- not sufficient in general. There are four cases to consider:
5801 -- a) If the attribute appears within a task body, the designated
5802 -- TCB is obtained by a call to Self.
5804 -- b) If the prefix of the attribute is the name of a task object,
5805 -- the designated TCB is the one stored in the corresponding record.
5807 -- c) If the prefix is a task type, the size is obtained from the
5808 -- size variable created for each task type
5810 -- d) If no storage_size was specified for the type , there is no
5811 -- size variable, and the value is a system-specific default.
5814 if In_Open_Scopes
(Ptyp
) then
5816 -- Storage_Size (Self)
5820 Make_Function_Call
(Loc
,
5822 New_Occurrence_Of
(RTE
(RE_Storage_Size
), Loc
),
5823 Parameter_Associations
=>
5825 Make_Function_Call
(Loc
,
5827 New_Occurrence_Of
(RTE
(RE_Self
), Loc
))))));
5829 elsif not Is_Entity_Name
(Pref
)
5830 or else not Is_Type
(Entity
(Pref
))
5832 -- Storage_Size (Rec (Obj).Size)
5836 Make_Function_Call
(Loc
,
5838 New_Occurrence_Of
(RTE
(RE_Storage_Size
), Loc
),
5839 Parameter_Associations
=>
5841 Make_Selected_Component
(Loc
,
5843 Unchecked_Convert_To
(
5844 Corresponding_Record_Type
(Ptyp
),
5845 New_Copy_Tree
(Pref
)),
5847 Make_Identifier
(Loc
, Name_uTask_Id
))))));
5849 elsif Present
(Storage_Size_Variable
(Ptyp
)) then
5851 -- Static storage size pragma given for type: retrieve value
5852 -- from its allocated storage variable.
5856 Make_Function_Call
(Loc
,
5857 Name
=> New_Occurrence_Of
(
5858 RTE
(RE_Adjust_Storage_Size
), Loc
),
5859 Parameter_Associations
=>
5862 Storage_Size_Variable
(Ptyp
), Loc
)))));
5864 -- Get system default
5868 Make_Function_Call
(Loc
,
5871 RTE
(RE_Default_Stack_Size
), Loc
))));
5874 Analyze_And_Resolve
(N
, Typ
);
5882 when Attribute_Stream_Size
=>
5884 Make_Integer_Literal
(Loc
, Intval
=> Get_Stream_Size
(Ptyp
)));
5885 Analyze_And_Resolve
(N
, Typ
);
5891 -- 1. Deal with enumeration types with holes
5892 -- 2. For floating-point, generate call to attribute function
5893 -- 3. For other cases, deal with constraint checking
5895 when Attribute_Succ
=> Succ
: declare
5896 Etyp
: constant Entity_Id
:= Base_Type
(Ptyp
);
5900 -- For enumeration types with non-standard representations, we
5901 -- expand typ'Succ (x) into
5903 -- Pos_To_Rep (Rep_To_Pos (x) + 1)
5905 -- If the representation is contiguous, we compute instead
5906 -- Lit1 + Rep_to_Pos (x+1), to catch invalid representations.
5908 if Is_Enumeration_Type
(Ptyp
)
5909 and then Present
(Enum_Pos_To_Rep
(Etyp
))
5911 if Has_Contiguous_Rep
(Etyp
) then
5913 Unchecked_Convert_To
(Ptyp
,
5916 Make_Integer_Literal
(Loc
,
5917 Enumeration_Rep
(First_Literal
(Ptyp
))),
5919 Make_Function_Call
(Loc
,
5922 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
5924 Parameter_Associations
=>
5926 Unchecked_Convert_To
(Ptyp
,
5929 Unchecked_Convert_To
(Standard_Integer
,
5930 Relocate_Node
(First
(Exprs
))),
5932 Make_Integer_Literal
(Loc
, 1))),
5933 Rep_To_Pos_Flag
(Ptyp
, Loc
))))));
5935 -- Add Boolean parameter True, to request program errror if
5936 -- we have a bad representation on our hands. Add False if
5937 -- checks are suppressed.
5939 Append_To
(Exprs
, Rep_To_Pos_Flag
(Ptyp
, Loc
));
5941 Make_Indexed_Component
(Loc
,
5944 (Enum_Pos_To_Rep
(Etyp
), Loc
),
5945 Expressions
=> New_List
(
5948 Make_Function_Call
(Loc
,
5951 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
5952 Parameter_Associations
=> Exprs
),
5953 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)))));
5956 Analyze_And_Resolve
(N
, Typ
);
5958 -- For floating-point, we transform 'Succ into a call to the Succ
5959 -- floating-point attribute function in Fat_xxx (xxx is root type)
5961 elsif Is_Floating_Point_Type
(Ptyp
) then
5963 -- Handle case of range check. The Do_Range_Check flag is set only
5964 -- in Check_Float_Overflow mode, and what we need is a specific
5965 -- check against typ'Last, since that is the only overflow case.
5968 Expr
: constant Node_Id
:= First
(Exprs
);
5970 if Do_Range_Check
(Expr
) then
5971 Set_Do_Range_Check
(Expr
, False);
5973 Make_Raise_Constraint_Error
(Loc
,
5976 Left_Opnd
=> Duplicate_Subexpr
(Expr
),
5978 Make_Attribute_Reference
(Loc
,
5979 Attribute_Name
=> Name_Last
,
5981 New_Occurrence_Of
(Base_Type
(Ptyp
), Loc
))),
5982 Reason
=> CE_Overflow_Check_Failed
),
5983 Suppress
=> All_Checks
);
5987 -- Transform into call to attribute function
5989 Expand_Fpt_Attribute_R
(N
);
5990 Analyze_And_Resolve
(N
, Typ
);
5992 -- For modular types, nothing to do (no overflow, since wraps)
5994 elsif Is_Modular_Integer_Type
(Ptyp
) then
5997 -- For other types, if argument is marked as needing a range check or
5998 -- overflow checking is enabled, we must generate a check.
6000 elsif not Overflow_Checks_Suppressed
(Ptyp
)
6001 or else Do_Range_Check
(First
(Exprs
))
6003 Set_Do_Range_Check
(First
(Exprs
), False);
6004 Expand_Pred_Succ_Attribute
(N
);
6012 -- Transforms X'Tag into a direct reference to the tag of X
6014 when Attribute_Tag
=> Tag
: declare
6016 Prefix_Is_Type
: Boolean;
6019 if Is_Entity_Name
(Pref
) and then Is_Type
(Entity
(Pref
)) then
6020 Ttyp
:= Entity
(Pref
);
6021 Prefix_Is_Type
:= True;
6024 Prefix_Is_Type
:= False;
6027 if Is_Class_Wide_Type
(Ttyp
) then
6028 Ttyp
:= Root_Type
(Ttyp
);
6031 Ttyp
:= Underlying_Type
(Ttyp
);
6033 -- Ada 2005: The type may be a synchronized tagged type, in which
6034 -- case the tag information is stored in the corresponding record.
6036 if Is_Concurrent_Type
(Ttyp
) then
6037 Ttyp
:= Corresponding_Record_Type
(Ttyp
);
6040 if Prefix_Is_Type
then
6042 -- For VMs we leave the type attribute unexpanded because
6043 -- there's not a dispatching table to reference.
6045 if Tagged_Type_Expansion
then
6047 Unchecked_Convert_To
(RTE
(RE_Tag
),
6049 (Node
(First_Elmt
(Access_Disp_Table
(Ttyp
))), Loc
)));
6050 Analyze_And_Resolve
(N
, RTE
(RE_Tag
));
6053 -- Ada 2005 (AI-251): The use of 'Tag in the sources always
6054 -- references the primary tag of the actual object. If 'Tag is
6055 -- applied to class-wide interface objects we generate code that
6056 -- displaces "this" to reference the base of the object.
6058 elsif Comes_From_Source
(N
)
6059 and then Is_Class_Wide_Type
(Etype
(Prefix
(N
)))
6060 and then Is_Interface
(Etype
(Prefix
(N
)))
6063 -- (To_Tag_Ptr (Prefix'Address)).all
6065 -- Note that Prefix'Address is recursively expanded into a call
6066 -- to Base_Address (Obj.Tag)
6068 -- Not needed for VM targets, since all handled by the VM
6070 if Tagged_Type_Expansion
then
6072 Make_Explicit_Dereference
(Loc
,
6073 Unchecked_Convert_To
(RTE
(RE_Tag_Ptr
),
6074 Make_Attribute_Reference
(Loc
,
6075 Prefix
=> Relocate_Node
(Pref
),
6076 Attribute_Name
=> Name_Address
))));
6077 Analyze_And_Resolve
(N
, RTE
(RE_Tag
));
6082 Make_Selected_Component
(Loc
,
6083 Prefix
=> Relocate_Node
(Pref
),
6085 New_Occurrence_Of
(First_Tag_Component
(Ttyp
), Loc
)));
6086 Analyze_And_Resolve
(N
, RTE
(RE_Tag
));
6094 -- Transforms 'Terminated attribute into a call to Terminated function
6096 when Attribute_Terminated
=> Terminated
:
6098 -- The prefix of Terminated is of a task interface class-wide type.
6100 -- terminated (Task_Id (Pref._disp_get_task_id));
6102 if Ada_Version
>= Ada_2005
6103 and then Ekind
(Ptyp
) = E_Class_Wide_Type
6104 and then Is_Interface
(Ptyp
)
6105 and then Is_Task_Interface
(Ptyp
)
6108 Make_Function_Call
(Loc
,
6110 New_Occurrence_Of
(RTE
(RE_Terminated
), Loc
),
6111 Parameter_Associations
=> New_List
(
6112 Make_Unchecked_Type_Conversion
(Loc
,
6114 New_Occurrence_Of
(RTE
(RO_ST_Task_Id
), Loc
),
6116 Make_Selected_Component
(Loc
,
6118 New_Copy_Tree
(Pref
),
6120 Make_Identifier
(Loc
, Name_uDisp_Get_Task_Id
))))));
6122 elsif Restricted_Profile
then
6124 Build_Call_With_Task
(Pref
, RTE
(RE_Restricted_Terminated
)));
6128 Build_Call_With_Task
(Pref
, RTE
(RE_Terminated
)));
6131 Analyze_And_Resolve
(N
, Standard_Boolean
);
6138 -- Transforms System'To_Address (X) and System.Address'Ref (X) into
6139 -- unchecked conversion from (integral) type of X to type address.
6141 when Attribute_To_Address | Attribute_Ref
=>
6143 Unchecked_Convert_To
(RTE
(RE_Address
),
6144 Relocate_Node
(First
(Exprs
))));
6145 Analyze_And_Resolve
(N
, RTE
(RE_Address
));
6151 when Attribute_To_Any
=> To_Any
: declare
6152 P_Type
: constant Entity_Id
:= Etype
(Pref
);
6153 Decls
: constant List_Id
:= New_List
;
6159 Relocate_Node
(First
(Exprs
))), Decls
));
6160 Insert_Actions
(N
, Decls
);
6161 Analyze_And_Resolve
(N
, RTE
(RE_Any
));
6168 -- Transforms 'Truncation into a call to the floating-point attribute
6169 -- function Truncation in Fat_xxx (where xxx is the root type).
6170 -- Expansion is avoided for cases the back end can handle directly.
6172 when Attribute_Truncation
=>
6173 if not Is_Inline_Floating_Point_Attribute
(N
) then
6174 Expand_Fpt_Attribute_R
(N
);
6181 when Attribute_TypeCode
=> TypeCode
: declare
6182 P_Type
: constant Entity_Id
:= Etype
(Pref
);
6183 Decls
: constant List_Id
:= New_List
;
6185 Rewrite
(N
, Build_TypeCode_Call
(Loc
, P_Type
, Decls
));
6186 Insert_Actions
(N
, Decls
);
6187 Analyze_And_Resolve
(N
, RTE
(RE_TypeCode
));
6190 -----------------------
6191 -- Unbiased_Rounding --
6192 -----------------------
6194 -- Transforms 'Unbiased_Rounding into a call to the floating-point
6195 -- attribute function Unbiased_Rounding in Fat_xxx (where xxx is the
6196 -- root type). Expansion is avoided for cases the back end can handle
6199 when Attribute_Unbiased_Rounding
=>
6200 if not Is_Inline_Floating_Point_Attribute
(N
) then
6201 Expand_Fpt_Attribute_R
(N
);
6208 when Attribute_UET_Address
=> UET_Address
: declare
6209 Ent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
6213 Make_Object_Declaration
(Loc
,
6214 Defining_Identifier
=> Ent
,
6215 Aliased_Present
=> True,
6216 Object_Definition
=>
6217 New_Occurrence_Of
(RTE
(RE_Address
), Loc
)));
6219 -- Construct name __gnat_xxx__SDP, where xxx is the unit name
6220 -- in normal external form.
6222 Get_External_Unit_Name_String
(Get_Unit_Name
(Pref
));
6223 Name_Buffer
(1 + 7 .. Name_Len
+ 7) := Name_Buffer
(1 .. Name_Len
);
6224 Name_Len
:= Name_Len
+ 7;
6225 Name_Buffer
(1 .. 7) := "__gnat_";
6226 Name_Buffer
(Name_Len
+ 1 .. Name_Len
+ 5) := "__SDP";
6227 Name_Len
:= Name_Len
+ 5;
6229 Set_Is_Imported
(Ent
);
6230 Set_Interface_Name
(Ent
,
6231 Make_String_Literal
(Loc
,
6232 Strval
=> String_From_Name_Buffer
));
6234 -- Set entity as internal to ensure proper Sprint output of its
6235 -- implicit importation.
6237 Set_Is_Internal
(Ent
);
6240 Make_Attribute_Reference
(Loc
,
6241 Prefix
=> New_Occurrence_Of
(Ent
, Loc
),
6242 Attribute_Name
=> Name_Address
));
6244 Analyze_And_Resolve
(N
, Typ
);
6251 when Attribute_Update
=>
6252 Expand_Update_Attribute
(N
);
6258 -- The processing for VADS_Size is shared with Size
6264 -- For enumeration types with a standard representation, and for all
6265 -- other types, Val is handled by the back end. For enumeration types
6266 -- with a non-standard representation we use the _Pos_To_Rep array that
6267 -- was created when the type was frozen.
6269 when Attribute_Val
=> Val
: declare
6270 Etyp
: constant Entity_Id
:= Base_Type
(Entity
(Pref
));
6273 if Is_Enumeration_Type
(Etyp
)
6274 and then Present
(Enum_Pos_To_Rep
(Etyp
))
6276 if Has_Contiguous_Rep
(Etyp
) then
6278 Rep_Node
: constant Node_Id
:=
6279 Unchecked_Convert_To
(Etyp
,
6282 Make_Integer_Literal
(Loc
,
6283 Enumeration_Rep
(First_Literal
(Etyp
))),
6285 (Convert_To
(Standard_Integer
,
6286 Relocate_Node
(First
(Exprs
))))));
6290 Unchecked_Convert_To
(Etyp
,
6293 Make_Integer_Literal
(Loc
,
6294 Enumeration_Rep
(First_Literal
(Etyp
))),
6296 Make_Function_Call
(Loc
,
6299 (TSS
(Etyp
, TSS_Rep_To_Pos
), Loc
),
6300 Parameter_Associations
=> New_List
(
6302 Rep_To_Pos_Flag
(Etyp
, Loc
))))));
6307 Make_Indexed_Component
(Loc
,
6308 Prefix
=> New_Occurrence_Of
(Enum_Pos_To_Rep
(Etyp
), Loc
),
6309 Expressions
=> New_List
(
6310 Convert_To
(Standard_Integer
,
6311 Relocate_Node
(First
(Exprs
))))));
6314 Analyze_And_Resolve
(N
, Typ
);
6316 -- If the argument is marked as requiring a range check then generate
6319 elsif Do_Range_Check
(First
(Exprs
)) then
6320 Generate_Range_Check
(First
(Exprs
), Etyp
, CE_Range_Check_Failed
);
6328 -- The code for valid is dependent on the particular types involved.
6329 -- See separate sections below for the generated code in each case.
6331 when Attribute_Valid
=> Valid
: declare
6332 Btyp
: Entity_Id
:= Base_Type
(Ptyp
);
6335 Save_Validity_Checks_On
: constant Boolean := Validity_Checks_On
;
6336 -- Save the validity checking mode. We always turn off validity
6337 -- checking during process of 'Valid since this is one place
6338 -- where we do not want the implicit validity checks to intefere
6339 -- with the explicit validity check that the programmer is doing.
6341 function Make_Range_Test
return Node_Id
;
6342 -- Build the code for a range test of the form
6343 -- Btyp!(Pref) in Btyp!(Ptyp'First) .. Btyp!(Ptyp'Last)
6345 ---------------------
6346 -- Make_Range_Test --
6347 ---------------------
6349 function Make_Range_Test
return Node_Id
is
6350 Temp
: constant Node_Id
:= Duplicate_Subexpr
(Pref
);
6353 -- The value whose validity is being checked has been captured in
6354 -- an object declaration. We certainly don't want this object to
6355 -- appear valid because the declaration initializes it.
6357 if Is_Entity_Name
(Temp
) then
6358 Set_Is_Known_Valid
(Entity
(Temp
), False);
6364 Unchecked_Convert_To
(Btyp
, Temp
),
6368 Unchecked_Convert_To
(Btyp
,
6369 Make_Attribute_Reference
(Loc
,
6370 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
6371 Attribute_Name
=> Name_First
)),
6373 Unchecked_Convert_To
(Btyp
,
6374 Make_Attribute_Reference
(Loc
,
6375 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
6376 Attribute_Name
=> Name_Last
))));
6377 end Make_Range_Test
;
6379 -- Start of processing for Attribute_Valid
6382 -- Do not expand sourced code 'Valid reference in CodePeer mode,
6383 -- will be handled by the back-end directly.
6385 if CodePeer_Mode
and then Comes_From_Source
(N
) then
6389 -- Turn off validity checks. We do not want any implicit validity
6390 -- checks to intefere with the explicit check from the attribute
6392 Validity_Checks_On
:= False;
6394 -- Retrieve the base type. Handle the case where the base type is a
6395 -- private enumeration type.
6397 if Is_Private_Type
(Btyp
) and then Present
(Full_View
(Btyp
)) then
6398 Btyp
:= Full_View
(Btyp
);
6401 -- Floating-point case. This case is handled by the Valid attribute
6402 -- code in the floating-point attribute run-time library.
6404 if Is_Floating_Point_Type
(Ptyp
) then
6410 case Float_Rep
(Btyp
) is
6412 -- The AAMP back end handles Valid for floating-point types
6415 Analyze_And_Resolve
(Pref
, Ptyp
);
6416 Set_Etype
(N
, Standard_Boolean
);
6420 Find_Fat_Info
(Ptyp
, Ftp
, Pkg
);
6422 -- If the floating-point object might be unaligned, we
6423 -- need to call the special routine Unaligned_Valid,
6424 -- which makes the needed copy, being careful not to
6425 -- load the value into any floating-point register.
6426 -- The argument in this case is obj'Address (see
6427 -- Unaligned_Valid routine in Fat_Gen).
6429 if Is_Possibly_Unaligned_Object
(Pref
) then
6430 Expand_Fpt_Attribute
6431 (N
, Pkg
, Name_Unaligned_Valid
,
6433 Make_Attribute_Reference
(Loc
,
6434 Prefix
=> Relocate_Node
(Pref
),
6435 Attribute_Name
=> Name_Address
)));
6437 -- In the normal case where we are sure the object is
6438 -- aligned, we generate a call to Valid, and the argument
6439 -- in this case is obj'Unrestricted_Access (after
6440 -- converting obj to the right floating-point type).
6443 Expand_Fpt_Attribute
6444 (N
, Pkg
, Name_Valid
,
6446 Make_Attribute_Reference
(Loc
,
6447 Prefix
=> Unchecked_Convert_To
(Ftp
, Pref
),
6448 Attribute_Name
=> Name_Unrestricted_Access
)));
6452 -- One more task, we still need a range check. Required
6453 -- only if we have a constraint, since the Valid routine
6454 -- catches infinities properly (infinities are never valid).
6456 -- The way we do the range check is simply to create the
6457 -- expression: Valid (N) and then Base_Type(Pref) in Typ.
6459 if not Subtypes_Statically_Match
(Ptyp
, Btyp
) then
6462 Left_Opnd
=> Relocate_Node
(N
),
6465 Left_Opnd
=> Convert_To
(Btyp
, Pref
),
6466 Right_Opnd
=> New_Occurrence_Of
(Ptyp
, Loc
))));
6470 -- Enumeration type with holes
6472 -- For enumeration types with holes, the Pos value constructed by
6473 -- the Enum_Rep_To_Pos function built in Exp_Ch3 called with a
6474 -- second argument of False returns minus one for an invalid value,
6475 -- and the non-negative pos value for a valid value, so the
6476 -- expansion of X'Valid is simply:
6478 -- type(X)'Pos (X) >= 0
6480 -- We can't quite generate it that way because of the requirement
6481 -- for the non-standard second argument of False in the resulting
6482 -- rep_to_pos call, so we have to explicitly create:
6484 -- _rep_to_pos (X, False) >= 0
6486 -- If we have an enumeration subtype, we also check that the
6487 -- value is in range:
6489 -- _rep_to_pos (X, False) >= 0
6491 -- (X >= type(X)'First and then type(X)'Last <= X)
6493 elsif Is_Enumeration_Type
(Ptyp
)
6494 and then Present
(Enum_Pos_To_Rep
(Btyp
))
6499 Make_Function_Call
(Loc
,
6501 New_Occurrence_Of
(TSS
(Btyp
, TSS_Rep_To_Pos
), Loc
),
6502 Parameter_Associations
=> New_List
(
6504 New_Occurrence_Of
(Standard_False
, Loc
))),
6505 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0));
6509 (Type_Low_Bound
(Ptyp
) /= Type_Low_Bound
(Btyp
)
6511 Type_High_Bound
(Ptyp
) /= Type_High_Bound
(Btyp
))
6513 -- The call to Make_Range_Test will create declarations
6514 -- that need a proper insertion point, but Pref is now
6515 -- attached to a node with no ancestor. Attach to tree
6516 -- even if it is to be rewritten below.
6518 Set_Parent
(Tst
, Parent
(N
));
6522 Left_Opnd
=> Make_Range_Test
,
6528 -- Fortran convention booleans
6530 -- For the very special case of Fortran convention booleans, the
6531 -- value is always valid, since it is an integer with the semantics
6532 -- that non-zero is true, and any value is permissible.
6534 elsif Is_Boolean_Type
(Ptyp
)
6535 and then Convention
(Ptyp
) = Convention_Fortran
6537 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
6539 -- For biased representations, we will be doing an unchecked
6540 -- conversion without unbiasing the result. That means that the range
6541 -- test has to take this into account, and the proper form of the
6544 -- Btyp!(Pref) < Btyp!(Ptyp'Range_Length)
6546 elsif Has_Biased_Representation
(Ptyp
) then
6547 Btyp
:= RTE
(RE_Unsigned_32
);
6551 Unchecked_Convert_To
(Btyp
, Duplicate_Subexpr
(Pref
)),
6553 Unchecked_Convert_To
(Btyp
,
6554 Make_Attribute_Reference
(Loc
,
6555 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
6556 Attribute_Name
=> Name_Range_Length
))));
6558 -- For all other scalar types, what we want logically is a
6561 -- X in type(X)'First .. type(X)'Last
6563 -- But that's precisely what won't work because of possible
6564 -- unwanted optimization (and indeed the basic motivation for
6565 -- the Valid attribute is exactly that this test does not work).
6566 -- What will work is:
6568 -- Btyp!(X) >= Btyp!(type(X)'First)
6570 -- Btyp!(X) <= Btyp!(type(X)'Last)
6572 -- where Btyp is an integer type large enough to cover the full
6573 -- range of possible stored values (i.e. it is chosen on the basis
6574 -- of the size of the type, not the range of the values). We write
6575 -- this as two tests, rather than a range check, so that static
6576 -- evaluation will easily remove either or both of the checks if
6577 -- they can be -statically determined to be true (this happens
6578 -- when the type of X is static and the range extends to the full
6579 -- range of stored values).
6581 -- Unsigned types. Note: it is safe to consider only whether the
6582 -- subtype is unsigned, since we will in that case be doing all
6583 -- unsigned comparisons based on the subtype range. Since we use the
6584 -- actual subtype object size, this is appropriate.
6586 -- For example, if we have
6588 -- subtype x is integer range 1 .. 200;
6589 -- for x'Object_Size use 8;
6591 -- Now the base type is signed, but objects of this type are bits
6592 -- unsigned, and doing an unsigned test of the range 1 to 200 is
6593 -- correct, even though a value greater than 127 looks signed to a
6594 -- signed comparison.
6596 elsif Is_Unsigned_Type
(Ptyp
) then
6597 if Esize
(Ptyp
) <= 32 then
6598 Btyp
:= RTE
(RE_Unsigned_32
);
6600 Btyp
:= RTE
(RE_Unsigned_64
);
6603 Rewrite
(N
, Make_Range_Test
);
6608 if Esize
(Ptyp
) <= Esize
(Standard_Integer
) then
6609 Btyp
:= Standard_Integer
;
6611 Btyp
:= Universal_Integer
;
6614 Rewrite
(N
, Make_Range_Test
);
6617 -- If a predicate is present, then we do the predicate test, even if
6618 -- within the predicate function (infinite recursion is warned about
6619 -- in Sem_Attr in that case).
6622 Pred_Func
: constant Entity_Id
:= Predicate_Function
(Ptyp
);
6625 if Present
(Pred_Func
) then
6628 Left_Opnd
=> Relocate_Node
(N
),
6629 Right_Opnd
=> Make_Predicate_Call
(Ptyp
, Pref
)));
6633 Analyze_And_Resolve
(N
, Standard_Boolean
);
6634 Validity_Checks_On
:= Save_Validity_Checks_On
;
6641 when Attribute_Valid_Scalars
=> Valid_Scalars
: declare
6645 if Present
(Underlying_Type
(Ptyp
)) then
6646 Ftyp
:= Underlying_Type
(Ptyp
);
6651 -- Replace by True if no scalar parts
6653 if not Scalar_Part_Present
(Ftyp
) then
6654 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
6656 -- For scalar types, Valid_Scalars is the same as Valid
6658 elsif Is_Scalar_Type
(Ftyp
) then
6660 Make_Attribute_Reference
(Loc
,
6661 Attribute_Name
=> Name_Valid
,
6664 -- For array types, we construct a function that determines if there
6665 -- are any non-valid scalar subcomponents, and call the function.
6666 -- We only do this for arrays whose component type needs checking
6668 elsif Is_Array_Type
(Ftyp
)
6669 and then Scalar_Part_Present
(Component_Type
(Ftyp
))
6672 Make_Function_Call
(Loc
,
6674 New_Occurrence_Of
(Build_Array_VS_Func
(Ftyp
, N
), Loc
),
6675 Parameter_Associations
=> New_List
(Pref
)));
6677 -- For record types, we construct a function that determines if there
6678 -- are any non-valid scalar subcomponents, and call the function.
6680 elsif Is_Record_Type
(Ftyp
)
6681 and then Nkind
(Type_Definition
(Declaration_Node
(Ftyp
))) =
6685 Make_Function_Call
(Loc
,
6687 New_Occurrence_Of
(Build_Record_VS_Func
(Ftyp
, N
), Loc
),
6688 Parameter_Associations
=> New_List
(Pref
)));
6690 -- Other record types or types with discriminants
6692 elsif Is_Record_Type
(Ftyp
) or else Has_Discriminants
(Ptyp
) then
6694 -- Build expression with list of equality tests
6702 X
:= New_Occurrence_Of
(Standard_True
, Loc
);
6703 C
:= First_Component_Or_Discriminant
(Ptyp
);
6704 while Present
(C
) loop
6705 if not Scalar_Part_Present
(Etype
(C
)) then
6707 elsif Is_Scalar_Type
(Etype
(C
)) then
6710 A
:= Name_Valid_Scalars
;
6717 Make_Attribute_Reference
(Loc
,
6718 Attribute_Name
=> A
,
6720 Make_Selected_Component
(Loc
,
6722 Duplicate_Subexpr
(Pref
, Name_Req
=> True),
6724 New_Occurrence_Of
(C
, Loc
))));
6726 Next_Component_Or_Discriminant
(C
);
6732 -- For all other types, result is True
6735 Rewrite
(N
, New_Occurrence_Of
(Standard_Boolean
, Loc
));
6738 -- Result is always boolean, but never static
6740 Analyze_And_Resolve
(N
, Standard_Boolean
);
6741 Set_Is_Static_Expression
(N
, False);
6748 -- Value attribute is handled in separate unit Exp_Imgv
6750 when Attribute_Value
=>
6751 Exp_Imgv
.Expand_Value_Attribute
(N
);
6757 -- The processing for Value_Size shares the processing for Size
6763 -- The processing for Version shares the processing for Body_Version
6769 -- Wide_Image attribute is handled in separate unit Exp_Imgv
6771 when Attribute_Wide_Image
=>
6772 Exp_Imgv
.Expand_Wide_Image_Attribute
(N
);
6774 ---------------------
6775 -- Wide_Wide_Image --
6776 ---------------------
6778 -- Wide_Wide_Image attribute is handled in separate unit Exp_Imgv
6780 when Attribute_Wide_Wide_Image
=>
6781 Exp_Imgv
.Expand_Wide_Wide_Image_Attribute
(N
);
6787 -- We expand typ'Wide_Value (X) into
6790 -- (Wide_String_To_String (X, Wide_Character_Encoding_Method))
6792 -- Wide_String_To_String is a runtime function that converts its wide
6793 -- string argument to String, converting any non-translatable characters
6794 -- into appropriate escape sequences. This preserves the required
6795 -- semantics of Wide_Value in all cases, and results in a very simple
6796 -- implementation approach.
6798 -- Note: for this approach to be fully standard compliant for the cases
6799 -- where typ is Wide_Character and Wide_Wide_Character, the encoding
6800 -- method must cover the entire character range (e.g. UTF-8). But that
6801 -- is a reasonable requirement when dealing with encoded character
6802 -- sequences. Presumably if one of the restrictive encoding mechanisms
6803 -- is in use such as Shift-JIS, then characters that cannot be
6804 -- represented using this encoding will not appear in any case.
6806 when Attribute_Wide_Value
=> Wide_Value
:
6809 Make_Attribute_Reference
(Loc
,
6811 Attribute_Name
=> Name_Value
,
6813 Expressions
=> New_List
(
6814 Make_Function_Call
(Loc
,
6816 New_Occurrence_Of
(RTE
(RE_Wide_String_To_String
), Loc
),
6818 Parameter_Associations
=> New_List
(
6819 Relocate_Node
(First
(Exprs
)),
6820 Make_Integer_Literal
(Loc
,
6821 Intval
=> Int
(Wide_Character_Encoding_Method
)))))));
6823 Analyze_And_Resolve
(N
, Typ
);
6826 ---------------------
6827 -- Wide_Wide_Value --
6828 ---------------------
6830 -- We expand typ'Wide_Value_Value (X) into
6833 -- (Wide_Wide_String_To_String (X, Wide_Character_Encoding_Method))
6835 -- Wide_Wide_String_To_String is a runtime function that converts its
6836 -- wide string argument to String, converting any non-translatable
6837 -- characters into appropriate escape sequences. This preserves the
6838 -- required semantics of Wide_Wide_Value in all cases, and results in a
6839 -- very simple implementation approach.
6841 -- It's not quite right where typ = Wide_Wide_Character, because the
6842 -- encoding method may not cover the whole character type ???
6844 when Attribute_Wide_Wide_Value
=> Wide_Wide_Value
:
6847 Make_Attribute_Reference
(Loc
,
6849 Attribute_Name
=> Name_Value
,
6851 Expressions
=> New_List
(
6852 Make_Function_Call
(Loc
,
6855 (RTE
(RE_Wide_Wide_String_To_String
), Loc
),
6857 Parameter_Associations
=> New_List
(
6858 Relocate_Node
(First
(Exprs
)),
6859 Make_Integer_Literal
(Loc
,
6860 Intval
=> Int
(Wide_Character_Encoding_Method
)))))));
6862 Analyze_And_Resolve
(N
, Typ
);
6863 end Wide_Wide_Value
;
6865 ---------------------
6866 -- Wide_Wide_Width --
6867 ---------------------
6869 -- Wide_Wide_Width attribute is handled in separate unit Exp_Imgv
6871 when Attribute_Wide_Wide_Width
=>
6872 Exp_Imgv
.Expand_Width_Attribute
(N
, Wide_Wide
);
6878 -- Wide_Width attribute is handled in separate unit Exp_Imgv
6880 when Attribute_Wide_Width
=>
6881 Exp_Imgv
.Expand_Width_Attribute
(N
, Wide
);
6887 -- Width attribute is handled in separate unit Exp_Imgv
6889 when Attribute_Width
=>
6890 Exp_Imgv
.Expand_Width_Attribute
(N
, Normal
);
6896 when Attribute_Write
=> Write
: declare
6897 P_Type
: constant Entity_Id
:= Entity
(Pref
);
6898 U_Type
: constant Entity_Id
:= Underlying_Type
(P_Type
);
6906 -- If no underlying type, we have an error that will be diagnosed
6907 -- elsewhere, so here we just completely ignore the expansion.
6913 -- Stream operations can appear in user code even if the restriction
6914 -- No_Streams is active (for example, when instantiating a predefined
6915 -- container). In that case rewrite the attribute as a Raise to
6916 -- prevent any run-time use.
6918 if Restriction_Active
(No_Streams
) then
6920 Make_Raise_Program_Error
(Sloc
(N
),
6921 Reason
=> PE_Stream_Operation_Not_Allowed
));
6922 Set_Etype
(N
, U_Type
);
6926 -- The simple case, if there is a TSS for Write, just call it
6928 Pname
:= Find_Stream_Subprogram
(P_Type
, TSS_Stream_Write
);
6930 if Present
(Pname
) then
6934 -- If there is a Stream_Convert pragma, use it, we rewrite
6936 -- sourcetyp'Output (stream, Item)
6940 -- strmtyp'Output (Stream, strmwrite (acttyp (Item)));
6942 -- where strmwrite is the given Write function that converts an
6943 -- argument of type sourcetyp or a type acctyp, from which it is
6944 -- derived to type strmtyp. The conversion to acttyp is required
6945 -- for the derived case.
6947 Prag
:= Get_Stream_Convert_Pragma
(P_Type
);
6949 if Present
(Prag
) then
6951 Next
(Next
(First
(Pragma_Argument_Associations
(Prag
))));
6952 Wfunc
:= Entity
(Expression
(Arg3
));
6955 Make_Attribute_Reference
(Loc
,
6956 Prefix
=> New_Occurrence_Of
(Etype
(Wfunc
), Loc
),
6957 Attribute_Name
=> Name_Output
,
6958 Expressions
=> New_List
(
6959 Relocate_Node
(First
(Exprs
)),
6960 Make_Function_Call
(Loc
,
6961 Name
=> New_Occurrence_Of
(Wfunc
, Loc
),
6962 Parameter_Associations
=> New_List
(
6963 OK_Convert_To
(Etype
(First_Formal
(Wfunc
)),
6964 Relocate_Node
(Next
(First
(Exprs
)))))))));
6969 -- For elementary types, we call the W_xxx routine directly
6971 elsif Is_Elementary_Type
(U_Type
) then
6972 Rewrite
(N
, Build_Elementary_Write_Call
(N
));
6978 elsif Is_Array_Type
(U_Type
) then
6979 Build_Array_Write_Procedure
(N
, U_Type
, Decl
, Pname
);
6980 Compile_Stream_Body_In_Scope
(N
, Decl
, U_Type
, Check
=> False);
6982 -- Tagged type case, use the primitive Write function. Note that
6983 -- this will dispatch in the class-wide case which is what we want
6985 elsif Is_Tagged_Type
(U_Type
) then
6986 Pname
:= Find_Prim_Op
(U_Type
, TSS_Stream_Write
);
6988 -- All other record type cases, including protected records.
6989 -- The latter only arise for expander generated code for
6990 -- handling shared passive partition access.
6994 (Is_Record_Type
(U_Type
) or else Is_Protected_Type
(U_Type
));
6996 -- Ada 2005 (AI-216): Program_Error is raised when executing
6997 -- the default implementation of the Write attribute of an
6998 -- Unchecked_Union type. However, if the 'Write reference is
6999 -- within the generated Output stream procedure, Write outputs
7000 -- the components, and the default values of the discriminant
7001 -- are streamed by the Output procedure itself.
7003 if Is_Unchecked_Union
(Base_Type
(U_Type
))
7004 and not Is_TSS
(Current_Scope
, TSS_Stream_Output
)
7007 Make_Raise_Program_Error
(Loc
,
7008 Reason
=> PE_Unchecked_Union_Restriction
));
7011 if Has_Discriminants
(U_Type
)
7013 (Discriminant_Default_Value
(First_Discriminant
(U_Type
)))
7015 Build_Mutable_Record_Write_Procedure
7016 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
7018 Build_Record_Write_Procedure
7019 (Loc
, Full_Base
(U_Type
), Decl
, Pname
);
7022 Insert_Action
(N
, Decl
);
7026 -- If we fall through, Pname is the procedure to be called
7028 Rewrite_Stream_Proc_Call
(Pname
);
7031 -- Component_Size is handled by the back end, unless the component size
7032 -- is known at compile time, which is always true in the packed array
7033 -- case. It is important that the packed array case is handled in the
7034 -- front end (see Eval_Attribute) since the back end would otherwise get
7035 -- confused by the equivalent packed array type.
7037 when Attribute_Component_Size
=>
7040 -- The following attributes are handled by the back end (except that
7041 -- static cases have already been evaluated during semantic processing,
7042 -- but in any case the back end should not count on this).
7044 -- The back end also handles the non-class-wide cases of Size
7046 when Attribute_Bit_Order |
7047 Attribute_Code_Address |
7048 Attribute_Definite |
7049 Attribute_Null_Parameter |
7050 Attribute_Passed_By_Reference |
7051 Attribute_Pool_Address |
7052 Attribute_Scalar_Storage_Order
=>
7055 -- The following attributes are also handled by the back end, but return
7056 -- a universal integer result, so may need a conversion for checking
7057 -- that the result is in range.
7059 when Attribute_Aft |
7060 Attribute_Max_Alignment_For_Allocation
=>
7061 Apply_Universal_Integer_Attribute_Checks
(N
);
7063 -- The following attributes should not appear at this stage, since they
7064 -- have already been handled by the analyzer (and properly rewritten
7065 -- with corresponding values or entities to represent the right values)
7067 when Attribute_Abort_Signal |
7068 Attribute_Address_Size |
7069 Attribute_Atomic_Always_Lock_Free |
7072 Attribute_Compiler_Version |
7073 Attribute_Default_Bit_Order |
7080 Attribute_Fast_Math |
7081 Attribute_First_Valid |
7082 Attribute_Has_Access_Values |
7083 Attribute_Has_Discriminants |
7084 Attribute_Has_Tagged_Values |
7086 Attribute_Last_Valid |
7087 Attribute_Library_Level |
7088 Attribute_Lock_Free |
7089 Attribute_Machine_Emax |
7090 Attribute_Machine_Emin |
7091 Attribute_Machine_Mantissa |
7092 Attribute_Machine_Overflows |
7093 Attribute_Machine_Radix |
7094 Attribute_Machine_Rounds |
7095 Attribute_Maximum_Alignment |
7096 Attribute_Model_Emin |
7097 Attribute_Model_Epsilon |
7098 Attribute_Model_Mantissa |
7099 Attribute_Model_Small |
7101 Attribute_Partition_ID |
7103 Attribute_Restriction_Set |
7104 Attribute_Safe_Emax |
7105 Attribute_Safe_First |
7106 Attribute_Safe_Large |
7107 Attribute_Safe_Last |
7108 Attribute_Safe_Small |
7110 Attribute_Signed_Zeros |
7112 Attribute_Storage_Unit |
7113 Attribute_Stub_Type |
7114 Attribute_System_Allocator_Alignment |
7115 Attribute_Target_Name |
7116 Attribute_Type_Class |
7117 Attribute_Type_Key |
7118 Attribute_Unconstrained_Array |
7119 Attribute_Universal_Literal_String |
7120 Attribute_Wchar_T_Size |
7121 Attribute_Word_Size
=>
7122 raise Program_Error
;
7124 -- The Asm_Input and Asm_Output attributes are not expanded at this
7125 -- stage, but will be eliminated in the expansion of the Asm call, see
7126 -- Exp_Intr for details. So the back end will never see these either.
7128 when Attribute_Asm_Input |
7129 Attribute_Asm_Output
=>
7133 -- Note: as mentioned earlier, individual sections of the above case
7134 -- statement assume there is no code after the case statement, and are
7135 -- legitimately allowed to execute return statements if they have nothing
7136 -- more to do, so DO NOT add code at this point.
7139 when RE_Not_Available
=>
7141 end Expand_N_Attribute_Reference
;
7143 --------------------------------
7144 -- Expand_Pred_Succ_Attribute --
7145 --------------------------------
7147 -- For typ'Pred (exp), we generate the check
7149 -- [constraint_error when exp = typ'Base'First]
7151 -- Similarly, for typ'Succ (exp), we generate the check
7153 -- [constraint_error when exp = typ'Base'Last]
7155 -- These checks are not generated for modular types, since the proper
7156 -- semantics for Succ and Pred on modular types is to wrap, not raise CE.
7157 -- We also suppress these checks if we are the right side of an assignment
7158 -- statement or the expression of an object declaration, where the flag
7159 -- Suppress_Assignment_Checks is set for the assignment/declaration.
7161 procedure Expand_Pred_Succ_Attribute
(N
: Node_Id
) is
7162 Loc
: constant Source_Ptr
:= Sloc
(N
);
7163 P
: constant Node_Id
:= Parent
(N
);
7167 if Attribute_Name
(N
) = Name_Pred
then
7173 if not Nkind_In
(P
, N_Assignment_Statement
, N_Object_Declaration
)
7174 or else not Suppress_Assignment_Checks
(P
)
7177 Make_Raise_Constraint_Error
(Loc
,
7181 Duplicate_Subexpr_Move_Checks
(First
(Expressions
(N
))),
7183 Make_Attribute_Reference
(Loc
,
7185 New_Occurrence_Of
(Base_Type
(Etype
(Prefix
(N
))), Loc
),
7186 Attribute_Name
=> Cnam
)),
7187 Reason
=> CE_Overflow_Check_Failed
));
7189 end Expand_Pred_Succ_Attribute
;
7191 -----------------------------
7192 -- Expand_Update_Attribute --
7193 -----------------------------
7195 procedure Expand_Update_Attribute
(N
: Node_Id
) is
7196 procedure Process_Component_Or_Element_Update
7201 -- Generate the statements necessary to update a single component or an
7202 -- element of the prefix. The code is inserted before the attribute N.
7203 -- Temp denotes the entity of the anonymous object created to reflect
7204 -- the changes in values. Comp is the component/index expression to be
7205 -- updated. Expr is an expression yielding the new value of Comp. Typ
7206 -- is the type of the prefix of attribute Update.
7208 procedure Process_Range_Update
7213 -- Generate the statements necessary to update a slice of the prefix.
7214 -- The code is inserted before the attribute N. Temp denotes the entity
7215 -- of the anonymous object created to reflect the changes in values.
7216 -- Comp is range of the slice to be updated. Expr is an expression
7217 -- yielding the new value of Comp. Typ is the type of the prefix of
7218 -- attribute Update.
7220 -----------------------------------------
7221 -- Process_Component_Or_Element_Update --
7222 -----------------------------------------
7224 procedure Process_Component_Or_Element_Update
7230 Loc
: constant Source_Ptr
:= Sloc
(Comp
);
7235 -- An array element may be modified by the following relations
7236 -- depending on the number of dimensions:
7238 -- 1 => Expr -- one dimensional update
7239 -- (1, ..., N) => Expr -- multi dimensional update
7241 -- The above forms are converted in assignment statements where the
7242 -- left hand side is an indexed component:
7244 -- Temp (1) := Expr; -- one dimensional update
7245 -- Temp (1, ..., N) := Expr; -- multi dimensional update
7247 if Is_Array_Type
(Typ
) then
7249 -- The index expressions of a multi dimensional array update
7250 -- appear as an aggregate.
7252 if Nkind
(Comp
) = N_Aggregate
then
7253 Exprs
:= New_Copy_List_Tree
(Expressions
(Comp
));
7255 Exprs
:= New_List
(Relocate_Node
(Comp
));
7259 Make_Indexed_Component
(Loc
,
7260 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
7261 Expressions
=> Exprs
);
7263 -- A record component update appears in the following form:
7267 -- The above relation is transformed into an assignment statement
7268 -- where the left hand side is a selected component:
7270 -- Temp.Comp := Expr;
7272 else pragma Assert
(Is_Record_Type
(Typ
));
7274 Make_Selected_Component
(Loc
,
7275 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
7276 Selector_Name
=> Relocate_Node
(Comp
));
7280 Make_Assignment_Statement
(Loc
,
7282 Expression
=> Relocate_Node
(Expr
)));
7283 end Process_Component_Or_Element_Update
;
7285 --------------------------
7286 -- Process_Range_Update --
7287 --------------------------
7289 procedure Process_Range_Update
7295 Index_Typ
: constant Entity_Id
:= Etype
(First_Index
(Typ
));
7296 Loc
: constant Source_Ptr
:= Sloc
(Comp
);
7300 -- A range update appears as
7302 -- (Low .. High => Expr)
7304 -- The above construct is transformed into a loop that iterates over
7305 -- the given range and modifies the corresponding array values to the
7308 -- for Index in Low .. High loop
7309 -- Temp (<Index_Typ> (Index)) := Expr;
7312 Index
:= Make_Temporary
(Loc
, 'I');
7315 Make_Loop_Statement
(Loc
,
7317 Make_Iteration_Scheme
(Loc
,
7318 Loop_Parameter_Specification
=>
7319 Make_Loop_Parameter_Specification
(Loc
,
7320 Defining_Identifier
=> Index
,
7321 Discrete_Subtype_Definition
=> Relocate_Node
(Comp
))),
7323 Statements
=> New_List
(
7324 Make_Assignment_Statement
(Loc
,
7326 Make_Indexed_Component
(Loc
,
7327 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
7328 Expressions
=> New_List
(
7329 Convert_To
(Index_Typ
,
7330 New_Occurrence_Of
(Index
, Loc
)))),
7331 Expression
=> Relocate_Node
(Expr
))),
7333 End_Label
=> Empty
));
7334 end Process_Range_Update
;
7338 Aggr
: constant Node_Id
:= First
(Expressions
(N
));
7339 Loc
: constant Source_Ptr
:= Sloc
(N
);
7340 Pref
: constant Node_Id
:= Prefix
(N
);
7341 Typ
: constant Entity_Id
:= Etype
(Pref
);
7347 -- Start of processing for Expand_Update_Attribute
7350 -- Create the anonymous object that stores the value of the prefix and
7351 -- reflects subsequent changes in value. Generate:
7353 -- Temp : <type of Pref> := Pref;
7355 Temp
:= Make_Temporary
(Loc
, 'T');
7358 Make_Object_Declaration
(Loc
,
7359 Defining_Identifier
=> Temp
,
7360 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
7361 Expression
=> Relocate_Node
(Pref
)));
7363 -- Process the update aggregate
7365 Assoc
:= First
(Component_Associations
(Aggr
));
7366 while Present
(Assoc
) loop
7367 Comp
:= First
(Choices
(Assoc
));
7368 Expr
:= Expression
(Assoc
);
7369 while Present
(Comp
) loop
7370 if Nkind
(Comp
) = N_Range
then
7371 Process_Range_Update
(Temp
, Comp
, Expr
, Typ
);
7373 Process_Component_Or_Element_Update
(Temp
, Comp
, Expr
, Typ
);
7382 -- The attribute is replaced by a reference to the anonymous object
7384 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
7386 end Expand_Update_Attribute
;
7392 procedure Find_Fat_Info
7394 Fat_Type
: out Entity_Id
;
7395 Fat_Pkg
: out RE_Id
)
7397 Rtyp
: constant Entity_Id
:= Root_Type
(T
);
7400 -- All we do is use the root type (historically this dealt with
7401 -- VAX-float .. to be cleaned up further later ???)
7405 if Fat_Type
= Standard_Short_Float
then
7406 Fat_Pkg
:= RE_Attr_Short_Float
;
7408 elsif Fat_Type
= Standard_Float
then
7409 Fat_Pkg
:= RE_Attr_Float
;
7411 elsif Fat_Type
= Standard_Long_Float
then
7412 Fat_Pkg
:= RE_Attr_Long_Float
;
7414 elsif Fat_Type
= Standard_Long_Long_Float
then
7415 Fat_Pkg
:= RE_Attr_Long_Long_Float
;
7417 -- Universal real (which is its own root type) is treated as being
7418 -- equivalent to Standard.Long_Long_Float, since it is defined to
7419 -- have the same precision as the longest Float type.
7421 elsif Fat_Type
= Universal_Real
then
7422 Fat_Type
:= Standard_Long_Long_Float
;
7423 Fat_Pkg
:= RE_Attr_Long_Long_Float
;
7426 raise Program_Error
;
7430 ----------------------------
7431 -- Find_Stream_Subprogram --
7432 ----------------------------
7434 function Find_Stream_Subprogram
7436 Nam
: TSS_Name_Type
) return Entity_Id
7438 Base_Typ
: constant Entity_Id
:= Base_Type
(Typ
);
7439 Ent
: constant Entity_Id
:= TSS
(Typ
, Nam
);
7441 function Is_Available
(Entity
: RE_Id
) return Boolean;
7442 pragma Inline
(Is_Available
);
7443 -- Function to check whether the specified run-time call is available
7444 -- in the run time used. In the case of a configurable run time, it
7445 -- is normal that some subprograms are not there.
7447 -- I don't understand this routine at all, why is this not just a
7448 -- call to RTE_Available? And if for some reason we need a different
7449 -- routine with different semantics, why is not in Rtsfind ???
7455 function Is_Available
(Entity
: RE_Id
) return Boolean is
7457 -- Assume that the unit will always be available when using a
7458 -- "normal" (not configurable) run time.
7460 return not Configurable_Run_Time_Mode
or else RTE_Available
(Entity
);
7463 -- Start of processing for Find_Stream_Subprogram
7466 if Present
(Ent
) then
7470 -- Stream attributes for strings are expanded into library calls. The
7471 -- following checks are disabled when the run-time is not available or
7472 -- when compiling predefined types due to bootstrap issues. As a result,
7473 -- the compiler will generate in-place stream routines for string types
7474 -- that appear in GNAT's library, but will generate calls via rtsfind
7475 -- to library routines for user code.
7477 -- ??? For now, disable this code for JVM, since this generates a
7478 -- VerifyError exception at run time on e.g. c330001.
7480 -- This is disabled for AAMP, to avoid creating dependences on files not
7481 -- supported in the AAMP library (such as s-fileio.adb).
7483 -- Note: In the case of using a configurable run time, it is very likely
7484 -- that stream routines for string types are not present (they require
7485 -- file system support). In this case, the specific stream routines for
7486 -- strings are not used, relying on the regular stream mechanism
7487 -- instead. That is why we include the test Is_Available when dealing
7488 -- with these cases.
7490 if VM_Target
/= JVM_Target
7491 and then not AAMP_On_Target
7493 not Is_Predefined_File_Name
(Unit_File_Name
(Current_Sem_Unit
))
7495 -- Storage_Array as defined in package System.Storage_Elements
7497 if Is_RTE
(Base_Typ
, RE_Storage_Array
) then
7499 -- Case of No_Stream_Optimizations restriction active
7501 if Restriction_Active
(No_Stream_Optimizations
) then
7502 if Nam
= TSS_Stream_Input
7503 and then Is_Available
(RE_Storage_Array_Input
)
7505 return RTE
(RE_Storage_Array_Input
);
7507 elsif Nam
= TSS_Stream_Output
7508 and then Is_Available
(RE_Storage_Array_Output
)
7510 return RTE
(RE_Storage_Array_Output
);
7512 elsif Nam
= TSS_Stream_Read
7513 and then Is_Available
(RE_Storage_Array_Read
)
7515 return RTE
(RE_Storage_Array_Read
);
7517 elsif Nam
= TSS_Stream_Write
7518 and then Is_Available
(RE_Storage_Array_Write
)
7520 return RTE
(RE_Storage_Array_Write
);
7522 elsif Nam
/= TSS_Stream_Input
and then
7523 Nam
/= TSS_Stream_Output
and then
7524 Nam
/= TSS_Stream_Read
and then
7525 Nam
/= TSS_Stream_Write
7527 raise Program_Error
;
7530 -- Restriction No_Stream_Optimizations is not set, so we can go
7531 -- ahead and optimize using the block IO forms of the routines.
7534 if Nam
= TSS_Stream_Input
7535 and then Is_Available
(RE_Storage_Array_Input_Blk_IO
)
7537 return RTE
(RE_Storage_Array_Input_Blk_IO
);
7539 elsif Nam
= TSS_Stream_Output
7540 and then Is_Available
(RE_Storage_Array_Output_Blk_IO
)
7542 return RTE
(RE_Storage_Array_Output_Blk_IO
);
7544 elsif Nam
= TSS_Stream_Read
7545 and then Is_Available
(RE_Storage_Array_Read_Blk_IO
)
7547 return RTE
(RE_Storage_Array_Read_Blk_IO
);
7549 elsif Nam
= TSS_Stream_Write
7550 and then Is_Available
(RE_Storage_Array_Write_Blk_IO
)
7552 return RTE
(RE_Storage_Array_Write_Blk_IO
);
7554 elsif Nam
/= TSS_Stream_Input
and then
7555 Nam
/= TSS_Stream_Output
and then
7556 Nam
/= TSS_Stream_Read
and then
7557 Nam
/= TSS_Stream_Write
7559 raise Program_Error
;
7563 -- Stream_Element_Array as defined in package Ada.Streams
7565 elsif Is_RTE
(Base_Typ
, RE_Stream_Element_Array
) then
7567 -- Case of No_Stream_Optimizations restriction active
7569 if Restriction_Active
(No_Stream_Optimizations
) then
7570 if Nam
= TSS_Stream_Input
7571 and then Is_Available
(RE_Stream_Element_Array_Input
)
7573 return RTE
(RE_Stream_Element_Array_Input
);
7575 elsif Nam
= TSS_Stream_Output
7576 and then Is_Available
(RE_Stream_Element_Array_Output
)
7578 return RTE
(RE_Stream_Element_Array_Output
);
7580 elsif Nam
= TSS_Stream_Read
7581 and then Is_Available
(RE_Stream_Element_Array_Read
)
7583 return RTE
(RE_Stream_Element_Array_Read
);
7585 elsif Nam
= TSS_Stream_Write
7586 and then Is_Available
(RE_Stream_Element_Array_Write
)
7588 return RTE
(RE_Stream_Element_Array_Write
);
7590 elsif Nam
/= TSS_Stream_Input
and then
7591 Nam
/= TSS_Stream_Output
and then
7592 Nam
/= TSS_Stream_Read
and then
7593 Nam
/= TSS_Stream_Write
7595 raise Program_Error
;
7598 -- Restriction No_Stream_Optimizations is not set, so we can go
7599 -- ahead and optimize using the block IO forms of the routines.
7602 if Nam
= TSS_Stream_Input
7603 and then Is_Available
(RE_Stream_Element_Array_Input_Blk_IO
)
7605 return RTE
(RE_Stream_Element_Array_Input_Blk_IO
);
7607 elsif Nam
= TSS_Stream_Output
7608 and then Is_Available
(RE_Stream_Element_Array_Output_Blk_IO
)
7610 return RTE
(RE_Stream_Element_Array_Output_Blk_IO
);
7612 elsif Nam
= TSS_Stream_Read
7613 and then Is_Available
(RE_Stream_Element_Array_Read_Blk_IO
)
7615 return RTE
(RE_Stream_Element_Array_Read_Blk_IO
);
7617 elsif Nam
= TSS_Stream_Write
7618 and then Is_Available
(RE_Stream_Element_Array_Write_Blk_IO
)
7620 return RTE
(RE_Stream_Element_Array_Write_Blk_IO
);
7622 elsif Nam
/= TSS_Stream_Input
and then
7623 Nam
/= TSS_Stream_Output
and then
7624 Nam
/= TSS_Stream_Read
and then
7625 Nam
/= TSS_Stream_Write
7627 raise Program_Error
;
7631 -- String as defined in package Ada
7633 elsif Base_Typ
= Standard_String
then
7635 -- Case of No_Stream_Optimizations restriction active
7637 if Restriction_Active
(No_Stream_Optimizations
) then
7638 if Nam
= TSS_Stream_Input
7639 and then Is_Available
(RE_String_Input
)
7641 return RTE
(RE_String_Input
);
7643 elsif Nam
= TSS_Stream_Output
7644 and then Is_Available
(RE_String_Output
)
7646 return RTE
(RE_String_Output
);
7648 elsif Nam
= TSS_Stream_Read
7649 and then Is_Available
(RE_String_Read
)
7651 return RTE
(RE_String_Read
);
7653 elsif Nam
= TSS_Stream_Write
7654 and then Is_Available
(RE_String_Write
)
7656 return RTE
(RE_String_Write
);
7658 elsif Nam
/= TSS_Stream_Input
and then
7659 Nam
/= TSS_Stream_Output
and then
7660 Nam
/= TSS_Stream_Read
and then
7661 Nam
/= TSS_Stream_Write
7663 raise Program_Error
;
7666 -- Restriction No_Stream_Optimizations is not set, so we can go
7667 -- ahead and optimize using the block IO forms of the routines.
7670 if Nam
= TSS_Stream_Input
7671 and then Is_Available
(RE_String_Input_Blk_IO
)
7673 return RTE
(RE_String_Input_Blk_IO
);
7675 elsif Nam
= TSS_Stream_Output
7676 and then Is_Available
(RE_String_Output_Blk_IO
)
7678 return RTE
(RE_String_Output_Blk_IO
);
7680 elsif Nam
= TSS_Stream_Read
7681 and then Is_Available
(RE_String_Read_Blk_IO
)
7683 return RTE
(RE_String_Read_Blk_IO
);
7685 elsif Nam
= TSS_Stream_Write
7686 and then Is_Available
(RE_String_Write_Blk_IO
)
7688 return RTE
(RE_String_Write_Blk_IO
);
7690 elsif Nam
/= TSS_Stream_Input
and then
7691 Nam
/= TSS_Stream_Output
and then
7692 Nam
/= TSS_Stream_Read
and then
7693 Nam
/= TSS_Stream_Write
7695 raise Program_Error
;
7699 -- Wide_String as defined in package Ada
7701 elsif Base_Typ
= Standard_Wide_String
then
7703 -- Case of No_Stream_Optimizations restriction active
7705 if Restriction_Active
(No_Stream_Optimizations
) then
7706 if Nam
= TSS_Stream_Input
7707 and then Is_Available
(RE_Wide_String_Input
)
7709 return RTE
(RE_Wide_String_Input
);
7711 elsif Nam
= TSS_Stream_Output
7712 and then Is_Available
(RE_Wide_String_Output
)
7714 return RTE
(RE_Wide_String_Output
);
7716 elsif Nam
= TSS_Stream_Read
7717 and then Is_Available
(RE_Wide_String_Read
)
7719 return RTE
(RE_Wide_String_Read
);
7721 elsif Nam
= TSS_Stream_Write
7722 and then Is_Available
(RE_Wide_String_Write
)
7724 return RTE
(RE_Wide_String_Write
);
7726 elsif Nam
/= TSS_Stream_Input
and then
7727 Nam
/= TSS_Stream_Output
and then
7728 Nam
/= TSS_Stream_Read
and then
7729 Nam
/= TSS_Stream_Write
7731 raise Program_Error
;
7734 -- Restriction No_Stream_Optimizations is not set, so we can go
7735 -- ahead and optimize using the block IO forms of the routines.
7738 if Nam
= TSS_Stream_Input
7739 and then Is_Available
(RE_Wide_String_Input_Blk_IO
)
7741 return RTE
(RE_Wide_String_Input_Blk_IO
);
7743 elsif Nam
= TSS_Stream_Output
7744 and then Is_Available
(RE_Wide_String_Output_Blk_IO
)
7746 return RTE
(RE_Wide_String_Output_Blk_IO
);
7748 elsif Nam
= TSS_Stream_Read
7749 and then Is_Available
(RE_Wide_String_Read_Blk_IO
)
7751 return RTE
(RE_Wide_String_Read_Blk_IO
);
7753 elsif Nam
= TSS_Stream_Write
7754 and then Is_Available
(RE_Wide_String_Write_Blk_IO
)
7756 return RTE
(RE_Wide_String_Write_Blk_IO
);
7758 elsif Nam
/= TSS_Stream_Input
and then
7759 Nam
/= TSS_Stream_Output
and then
7760 Nam
/= TSS_Stream_Read
and then
7761 Nam
/= TSS_Stream_Write
7763 raise Program_Error
;
7767 -- Wide_Wide_String as defined in package Ada
7769 elsif Base_Typ
= Standard_Wide_Wide_String
then
7771 -- Case of No_Stream_Optimizations restriction active
7773 if Restriction_Active
(No_Stream_Optimizations
) then
7774 if Nam
= TSS_Stream_Input
7775 and then Is_Available
(RE_Wide_Wide_String_Input
)
7777 return RTE
(RE_Wide_Wide_String_Input
);
7779 elsif Nam
= TSS_Stream_Output
7780 and then Is_Available
(RE_Wide_Wide_String_Output
)
7782 return RTE
(RE_Wide_Wide_String_Output
);
7784 elsif Nam
= TSS_Stream_Read
7785 and then Is_Available
(RE_Wide_Wide_String_Read
)
7787 return RTE
(RE_Wide_Wide_String_Read
);
7789 elsif Nam
= TSS_Stream_Write
7790 and then Is_Available
(RE_Wide_Wide_String_Write
)
7792 return RTE
(RE_Wide_Wide_String_Write
);
7794 elsif Nam
/= TSS_Stream_Input
and then
7795 Nam
/= TSS_Stream_Output
and then
7796 Nam
/= TSS_Stream_Read
and then
7797 Nam
/= TSS_Stream_Write
7799 raise Program_Error
;
7802 -- Restriction No_Stream_Optimizations is not set, so we can go
7803 -- ahead and optimize using the block IO forms of the routines.
7806 if Nam
= TSS_Stream_Input
7807 and then Is_Available
(RE_Wide_Wide_String_Input_Blk_IO
)
7809 return RTE
(RE_Wide_Wide_String_Input_Blk_IO
);
7811 elsif Nam
= TSS_Stream_Output
7812 and then Is_Available
(RE_Wide_Wide_String_Output_Blk_IO
)
7814 return RTE
(RE_Wide_Wide_String_Output_Blk_IO
);
7816 elsif Nam
= TSS_Stream_Read
7817 and then Is_Available
(RE_Wide_Wide_String_Read_Blk_IO
)
7819 return RTE
(RE_Wide_Wide_String_Read_Blk_IO
);
7821 elsif Nam
= TSS_Stream_Write
7822 and then Is_Available
(RE_Wide_Wide_String_Write_Blk_IO
)
7824 return RTE
(RE_Wide_Wide_String_Write_Blk_IO
);
7826 elsif Nam
/= TSS_Stream_Input
and then
7827 Nam
/= TSS_Stream_Output
and then
7828 Nam
/= TSS_Stream_Read
and then
7829 Nam
/= TSS_Stream_Write
7831 raise Program_Error
;
7837 if Is_Tagged_Type
(Typ
) and then Is_Derived_Type
(Typ
) then
7838 return Find_Prim_Op
(Typ
, Nam
);
7840 return Find_Inherited_TSS
(Typ
, Nam
);
7842 end Find_Stream_Subprogram
;
7848 function Full_Base
(T
: Entity_Id
) return Entity_Id
is
7852 BT
:= Base_Type
(T
);
7854 if Is_Private_Type
(BT
)
7855 and then Present
(Full_View
(BT
))
7857 BT
:= Full_View
(BT
);
7863 -----------------------
7864 -- Get_Index_Subtype --
7865 -----------------------
7867 function Get_Index_Subtype
(N
: Node_Id
) return Node_Id
is
7868 P_Type
: Entity_Id
:= Etype
(Prefix
(N
));
7873 if Is_Access_Type
(P_Type
) then
7874 P_Type
:= Designated_Type
(P_Type
);
7877 if No
(Expressions
(N
)) then
7880 J
:= UI_To_Int
(Expr_Value
(First
(Expressions
(N
))));
7883 Indx
:= First_Index
(P_Type
);
7889 return Etype
(Indx
);
7890 end Get_Index_Subtype
;
7892 -------------------------------
7893 -- Get_Stream_Convert_Pragma --
7894 -------------------------------
7896 function Get_Stream_Convert_Pragma
(T
: Entity_Id
) return Node_Id
is
7901 -- Note: we cannot use Get_Rep_Pragma here because of the peculiarity
7902 -- that a stream convert pragma for a tagged type is not inherited from
7903 -- its parent. Probably what is wrong here is that it is basically
7904 -- incorrect to consider a stream convert pragma to be a representation
7905 -- pragma at all ???
7907 N
:= First_Rep_Item
(Implementation_Base_Type
(T
));
7908 while Present
(N
) loop
7909 if Nkind
(N
) = N_Pragma
7910 and then Pragma_Name
(N
) = Name_Stream_Convert
7912 -- For tagged types this pragma is not inherited, so we
7913 -- must verify that it is defined for the given type and
7917 Entity
(Expression
(First
(Pragma_Argument_Associations
(N
))));
7919 if not Is_Tagged_Type
(T
)
7921 or else (Is_Private_Type
(Typ
) and then T
= Full_View
(Typ
))
7931 end Get_Stream_Convert_Pragma
;
7933 ---------------------------------
7934 -- Is_Constrained_Packed_Array --
7935 ---------------------------------
7937 function Is_Constrained_Packed_Array
(Typ
: Entity_Id
) return Boolean is
7938 Arr
: Entity_Id
:= Typ
;
7941 if Is_Access_Type
(Arr
) then
7942 Arr
:= Designated_Type
(Arr
);
7945 return Is_Array_Type
(Arr
)
7946 and then Is_Constrained
(Arr
)
7947 and then Present
(Packed_Array_Impl_Type
(Arr
));
7948 end Is_Constrained_Packed_Array
;
7950 ----------------------------------------
7951 -- Is_Inline_Floating_Point_Attribute --
7952 ----------------------------------------
7954 function Is_Inline_Floating_Point_Attribute
(N
: Node_Id
) return Boolean is
7955 Id
: constant Attribute_Id
:= Get_Attribute_Id
(Attribute_Name
(N
));
7957 function Is_GCC_Target
return Boolean;
7958 -- Return True if we are using a GCC target/back-end
7959 -- ??? Note: the implementation is kludgy/fragile
7965 function Is_GCC_Target
return Boolean is
7967 return VM_Target
= No_VM
and then not CodePeer_Mode
7968 and then not AAMP_On_Target
;
7971 -- Start of processing for Exp_Attr
7974 -- Machine and Model can be expanded by the GCC backend only
7976 if Id
= Attribute_Machine
or else Id
= Attribute_Model
then
7977 return Is_GCC_Target
;
7979 -- Remaining cases handled by all back ends are Rounding and Truncation
7980 -- when appearing as the operand of a conversion to some integer type.
7982 elsif Nkind
(Parent
(N
)) /= N_Type_Conversion
7983 or else not Is_Integer_Type
(Etype
(Parent
(N
)))
7988 -- Here we are in the integer conversion context
7990 -- Very probably we should also recognize the cases of Machine_Rounding
7991 -- and unbiased rounding in this conversion context, but the back end is
7992 -- not yet prepared to handle these cases ???
7994 return Id
= Attribute_Rounding
or else Id
= Attribute_Truncation
;
7995 end Is_Inline_Floating_Point_Attribute
;