1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 2001-2017, 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 Casing
; use Casing
;
28 with Checks
; use Checks
;
29 with Einfo
; use Einfo
;
30 with Exp_Util
; use Exp_Util
;
32 with Namet
; use Namet
;
33 with Nmake
; use Nmake
;
34 with Nlists
; use Nlists
;
36 with Rtsfind
; use Rtsfind
;
37 with Sem_Aux
; use Sem_Aux
;
38 with Sem_Res
; use Sem_Res
;
39 with Sem_Util
; use Sem_Util
;
40 with Sinfo
; use Sinfo
;
41 with Snames
; use Snames
;
42 with Stand
; use Stand
;
43 with Stringt
; use Stringt
;
44 with Tbuild
; use Tbuild
;
45 with Ttypes
; use Ttypes
;
46 with Uintp
; use Uintp
;
47 with Urealp
; use Urealp
;
49 package body Exp_Imgv
is
51 function Has_Decimal_Small
(E
: Entity_Id
) return Boolean;
52 -- Applies to all entities. True for a Decimal_Fixed_Point_Type, or an
53 -- Ordinary_Fixed_Point_Type with a small that is a negative power of ten.
54 -- Shouldn't this be in einfo.adb or sem_aux.adb???
56 procedure Rewrite_Object_Image
61 -- AI12-00124: Rewrite attribute 'Image when it is applied to an object
62 -- reference as an attribute applied to a type. N denotes the node to be
63 -- rewritten, Pref denotes the prefix of the 'Image attribute, and Name
64 -- and Str_Typ specify which specific string type and 'Image attribute to
65 -- apply (e.g. Name_Wide_Image and Standard_Wide_String).
67 ------------------------------------
68 -- Build_Enumeration_Image_Tables --
69 ------------------------------------
71 procedure Build_Enumeration_Image_Tables
(E
: Entity_Id
; N
: Node_Id
) is
72 Loc
: constant Source_Ptr
:= Sloc
(E
);
83 -- Nothing to do for other than a root enumeration type
85 if E
/= Root_Type
(E
) then
88 -- Nothing to do if pragma Discard_Names applies
90 elsif Discard_Names
(E
) then
94 -- Otherwise tables need constructing
98 Lit
:= First_Literal
(E
);
104 Make_Integer_Literal
(Loc
, UI_From_Int
(Len
)));
109 Get_Unqualified_Decoded_Name_String
(Chars
(Lit
));
111 if Name_Buffer
(1) /= ''' then
112 Set_Casing
(All_Upper_Case
);
115 Store_String_Chars
(Name_Buffer
(1 .. Name_Len
));
116 Len
:= Len
+ Int
(Name_Len
);
120 if Len
< Int
(2 ** (8 - 1)) then
121 Ityp
:= Standard_Integer_8
;
122 elsif Len
< Int
(2 ** (16 - 1)) then
123 Ityp
:= Standard_Integer_16
;
125 Ityp
:= Standard_Integer_32
;
131 Make_Defining_Identifier
(Loc
,
132 Chars
=> New_External_Name
(Chars
(E
), 'S'));
135 Make_Defining_Identifier
(Loc
,
136 Chars
=> New_External_Name
(Chars
(E
), 'N'));
138 Set_Lit_Strings
(E
, Estr
);
139 Set_Lit_Indexes
(E
, Eind
);
143 Make_Object_Declaration
(Loc
,
144 Defining_Identifier
=> Estr
,
145 Constant_Present
=> True,
147 New_Occurrence_Of
(Standard_String
, Loc
),
149 Make_String_Literal
(Loc
,
152 Make_Object_Declaration
(Loc
,
153 Defining_Identifier
=> Eind
,
154 Constant_Present
=> True,
157 Make_Constrained_Array_Definition
(Loc
,
158 Discrete_Subtype_Definitions
=> New_List
(
160 Low_Bound
=> Make_Integer_Literal
(Loc
, 0),
161 High_Bound
=> Make_Integer_Literal
(Loc
, Nlit
))),
162 Component_Definition
=>
163 Make_Component_Definition
(Loc
,
164 Aliased_Present
=> False,
165 Subtype_Indication
=> New_Occurrence_Of
(Ityp
, Loc
))),
169 Expressions
=> Ind
))),
170 Suppress
=> All_Checks
);
171 end Build_Enumeration_Image_Tables
;
173 ----------------------------
174 -- Expand_Image_Attribute --
175 ----------------------------
177 -- For all cases other than user-defined enumeration types, the scheme
178 -- is as follows. First we insert the following code:
180 -- Snn : String (1 .. rt'Width);
182 -- Image_xx (tv, Snn, Pnn [,pm]);
184 -- and then Expr is replaced by Snn (1 .. Pnn)
186 -- In the above expansion:
188 -- rt is the root type of the expression
189 -- tv is the expression with the value, usually a type conversion
190 -- pm is an extra parameter present in some cases
192 -- The following table shows tv, xx, and (if used) pm for the various
193 -- possible types of the argument:
195 -- For types whose root type is Character
197 -- tv = Character (Expr)
199 -- For types whose root type is Boolean
201 -- tv = Boolean (Expr)
203 -- For signed integer types with size <= Integer'Size
205 -- tv = Integer (Expr)
207 -- For other signed integer types
208 -- xx = Long_Long_Integer
209 -- tv = Long_Long_Integer (Expr)
211 -- For modular types with modulus <= System.Unsigned_Types.Unsigned
213 -- tv = System.Unsigned_Types.Unsigned (Expr)
215 -- For other modular integer types
216 -- xx = Long_Long_Unsigned
217 -- tv = System.Unsigned_Types.Long_Long_Unsigned (Expr)
219 -- For types whose root type is Wide_Character
220 -- xx = Wide_Character
221 -- tv = Wide_Character (Expr)
222 -- pm = Boolean, true if Ada 2005 mode, False otherwise
224 -- For types whose root type is Wide_Wide_Character
225 -- xx = Wide_Wide_Character
226 -- tv = Wide_Wide_Character (Expr)
228 -- For floating-point types
229 -- xx = Floating_Point
230 -- tv = Long_Long_Float (Expr)
231 -- pm = typ'Digits (typ = subtype of expression)
233 -- For ordinary fixed-point types
234 -- xx = Ordinary_Fixed_Point
235 -- tv = Long_Long_Float (Expr)
236 -- pm = typ'Aft (typ = subtype of expression)
238 -- For decimal fixed-point types with size = Integer'Size
240 -- tv = Integer (Expr)
241 -- pm = typ'Scale (typ = subtype of expression)
243 -- For decimal fixed-point types with size > Integer'Size
244 -- xx = Long_Long_Decimal
245 -- tv = Long_Long_Integer?(Expr) [convert with no scaling]
246 -- pm = typ'Scale (typ = subtype of expression)
248 -- For enumeration types other than those declared packages Standard
249 -- or System, Snn, Pnn, are expanded as above, but the call looks like:
251 -- Image_Enumeration_NN (rt'Pos (X), Snn, Pnn, typS, typI'Address)
253 -- where rt is the root type of the expression, and typS and typI are
254 -- the entities constructed as described in the spec for the procedure
255 -- Build_Enumeration_Image_Tables and NN is 32/16/8 depending on the
256 -- element type of Lit_Indexes. The rewriting of the expression to
257 -- Snn (1 .. Pnn) then occurs as in the other cases. A special case is
258 -- when pragma Discard_Names applies, in which case we replace expr by:
260 -- (rt'Pos (expr))'Img
262 -- So that the result is a space followed by the decimal value for the
263 -- position of the enumeration value in the enumeration type.
265 procedure Expand_Image_Attribute
(N
: Node_Id
) is
266 Loc
: constant Source_Ptr
:= Sloc
(N
);
267 Exprs
: constant List_Id
:= Expressions
(N
);
268 Expr
: constant Node_Id
:= Relocate_Node
(First
(Exprs
));
269 Pref
: constant Node_Id
:= Prefix
(N
);
271 procedure Expand_User_Defined_Enumeration_Image
;
272 -- Expand attribute 'Image in user-defined enumeration types, avoiding
275 function Is_User_Defined_Enumeration_Type
276 (Typ
: Entity_Id
) return Boolean;
277 -- Return True if Typ is a user-defined enumeration type
279 -------------------------------------------
280 -- Expand_User_Defined_Enumeration_Image --
281 -------------------------------------------
283 procedure Expand_User_Defined_Enumeration_Image
is
284 Ins_List
: constant List_Id
:= New_List
;
285 P1_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
286 P2_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
287 P3_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
288 P4_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
289 Ptyp
: constant Entity_Id
:= Entity
(Pref
);
290 Rtyp
: constant Entity_Id
:= Root_Type
(Ptyp
);
291 S1_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
294 -- Apply a validity check, since it is a bit drastic to get a
295 -- completely junk image value for an invalid value.
297 if not Expr_Known_Valid
(Expr
) then
298 Insert_Valid_Check
(Expr
);
302 -- P1 : constant Natural := Pos;
305 Make_Object_Declaration
(Loc
,
306 Defining_Identifier
=> P1_Id
,
308 New_Occurrence_Of
(Standard_Natural
, Loc
),
309 Constant_Present
=> True,
311 Convert_To
(Standard_Natural
,
312 Make_Attribute_Reference
(Loc
,
313 Attribute_Name
=> Name_Pos
,
314 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
315 Expressions
=> New_List
(Expr
)))));
317 -- Compute the index of the string start, generating:
318 -- P2 : constant Natural := call_put_enumN (P1);
321 Make_Object_Declaration
(Loc
,
322 Defining_Identifier
=> P2_Id
,
324 New_Occurrence_Of
(Standard_Natural
, Loc
),
325 Constant_Present
=> True,
327 Convert_To
(Standard_Natural
,
328 Make_Indexed_Component
(Loc
,
330 New_Occurrence_Of
(Lit_Indexes
(Rtyp
), Loc
),
332 New_List
(New_Occurrence_Of
(P1_Id
, Loc
))))));
334 -- Compute the index of the next value, generating:
335 -- P3 : constant Natural := call_put_enumN (P1 + 1);
338 Add_Node
: constant Node_Id
:= New_Op_Node
(N_Op_Add
, Loc
);
341 Set_Left_Opnd
(Add_Node
, New_Occurrence_Of
(P1_Id
, Loc
));
342 Set_Right_Opnd
(Add_Node
, Make_Integer_Literal
(Loc
, 1));
345 Make_Object_Declaration
(Loc
,
346 Defining_Identifier
=> P3_Id
,
348 New_Occurrence_Of
(Standard_Natural
, Loc
),
349 Constant_Present
=> True,
351 Convert_To
(Standard_Natural
,
352 Make_Indexed_Component
(Loc
,
354 New_Occurrence_Of
(Lit_Indexes
(Rtyp
), Loc
),
356 New_List
(Add_Node
)))));
360 -- S4 : String renames call_put_enumS (S2 .. S3 - 1);
363 Sub_Node
: constant Node_Id
:= New_Op_Node
(N_Op_Subtract
, Loc
);
366 Set_Left_Opnd
(Sub_Node
, New_Occurrence_Of
(P3_Id
, Loc
));
367 Set_Right_Opnd
(Sub_Node
, Make_Integer_Literal
(Loc
, 1));
370 Make_Object_Renaming_Declaration
(Loc
,
371 Defining_Identifier
=> P4_Id
,
373 New_Occurrence_Of
(Standard_String
, Loc
),
377 New_Occurrence_Of
(Lit_Strings
(Rtyp
), Loc
),
380 Low_Bound
=> New_Occurrence_Of
(P2_Id
, Loc
),
381 High_Bound
=> Sub_Node
))));
385 -- subtype S1 is string (1 .. P3 - P2);
388 HB
: constant Node_Id
:= New_Op_Node
(N_Op_Subtract
, Loc
);
391 Set_Left_Opnd
(HB
, New_Occurrence_Of
(P3_Id
, Loc
));
392 Set_Right_Opnd
(HB
, New_Occurrence_Of
(P2_Id
, Loc
));
395 Make_Subtype_Declaration
(Loc
,
396 Defining_Identifier
=> S1_Id
,
397 Subtype_Indication
=>
398 Make_Subtype_Indication
(Loc
,
400 New_Occurrence_Of
(Standard_String
, Loc
),
402 Make_Index_Or_Discriminant_Constraint
(Loc
,
403 Constraints
=> New_List
(
405 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
406 High_Bound
=> HB
))))));
409 -- Insert all the above declarations before N. We suppress checks
410 -- because everything is in range at this stage.
412 Insert_Actions
(N
, Ins_List
, Suppress
=> All_Checks
);
415 Unchecked_Convert_To
(S1_Id
, New_Occurrence_Of
(P4_Id
, Loc
)));
417 Analyze_And_Resolve
(N
, Standard_String
);
418 end Expand_User_Defined_Enumeration_Image
;
420 --------------------------------------
421 -- Is_User_Defined_Enumeration_Type --
422 --------------------------------------
424 function Is_User_Defined_Enumeration_Type
425 (Typ
: Entity_Id
) return Boolean is
427 return Ekind
(Typ
) = E_Enumeration_Type
428 and then Typ
/= Standard_Boolean
429 and then Typ
/= Standard_Character
430 and then Typ
/= Standard_Wide_Character
431 and then Typ
/= Standard_Wide_Wide_Character
;
432 end Is_User_Defined_Enumeration_Type
;
439 Tent
: Entity_Id
:= Empty
;
441 Proc_Ent
: Entity_Id
;
445 -- List of arguments for run-time procedure call
448 -- List of actions to be inserted
450 Snn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
451 Pnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
454 if Is_Object_Image
(Pref
) then
455 Rewrite_Object_Image
(N
, Pref
, Name_Image
, Standard_String
);
458 -- Enable speed-optimized expansion of user-defined enumeration types
459 -- if we are compiling with optimizations enabled and enumeration type
460 -- literals are generated. Otherwise the call will be expanded into a
461 -- call to the runtime library.
463 elsif Optimization_Level
> 0
464 and then not Global_Discard_Names
465 and then Is_User_Defined_Enumeration_Type
(Root_Type
(Entity
(Pref
)))
467 Expand_User_Defined_Enumeration_Image
;
471 Ptyp
:= Entity
(Pref
);
472 Rtyp
:= Root_Type
(Ptyp
);
474 -- Build declarations of Snn and Pnn to be inserted
476 Ins_List
:= New_List
(
478 -- Snn : String (1 .. typ'Width);
480 Make_Object_Declaration
(Loc
,
481 Defining_Identifier
=> Snn
,
483 Make_Subtype_Indication
(Loc
,
484 Subtype_Mark
=> New_Occurrence_Of
(Standard_String
, Loc
),
486 Make_Index_Or_Discriminant_Constraint
(Loc
,
487 Constraints
=> New_List
(
489 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
491 Make_Attribute_Reference
(Loc
,
492 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
),
493 Attribute_Name
=> Name_Width
)))))),
497 Make_Object_Declaration
(Loc
,
498 Defining_Identifier
=> Pnn
,
499 Object_Definition
=> New_Occurrence_Of
(Standard_Natural
, Loc
)));
501 -- Set Imid (RE_Id of procedure to call), and Tent, target for the
502 -- type conversion of the first argument for all possibilities.
506 if Rtyp
= Standard_Boolean
then
507 Imid
:= RE_Image_Boolean
;
510 -- For standard character, we have to select the version which handles
511 -- soft hyphen correctly, based on the version of Ada in use (this is
512 -- ugly, but we have no choice).
514 elsif Rtyp
= Standard_Character
then
515 if Ada_Version
< Ada_2005
then
516 Imid
:= RE_Image_Character
;
518 Imid
:= RE_Image_Character_05
;
523 elsif Rtyp
= Standard_Wide_Character
then
524 Imid
:= RE_Image_Wide_Character
;
527 elsif Rtyp
= Standard_Wide_Wide_Character
then
528 Imid
:= RE_Image_Wide_Wide_Character
;
531 elsif Is_Signed_Integer_Type
(Rtyp
) then
532 if Esize
(Rtyp
) <= Esize
(Standard_Integer
) then
533 Imid
:= RE_Image_Integer
;
534 Tent
:= Standard_Integer
;
536 Imid
:= RE_Image_Long_Long_Integer
;
537 Tent
:= Standard_Long_Long_Integer
;
540 elsif Is_Modular_Integer_Type
(Rtyp
) then
541 if Modulus
(Rtyp
) <= Modulus
(RTE
(RE_Unsigned
)) then
542 Imid
:= RE_Image_Unsigned
;
543 Tent
:= RTE
(RE_Unsigned
);
545 Imid
:= RE_Image_Long_Long_Unsigned
;
546 Tent
:= RTE
(RE_Long_Long_Unsigned
);
549 elsif Is_Fixed_Point_Type
(Rtyp
) and then Has_Decimal_Small
(Rtyp
) then
550 if UI_To_Int
(Esize
(Rtyp
)) <= Standard_Integer_Size
then
551 Imid
:= RE_Image_Decimal
;
552 Tent
:= Standard_Integer
;
554 Imid
:= RE_Image_Long_Long_Decimal
;
555 Tent
:= Standard_Long_Long_Integer
;
558 elsif Is_Ordinary_Fixed_Point_Type
(Rtyp
) then
559 Imid
:= RE_Image_Ordinary_Fixed_Point
;
560 Tent
:= Standard_Long_Long_Float
;
562 elsif Is_Floating_Point_Type
(Rtyp
) then
563 Imid
:= RE_Image_Floating_Point
;
564 Tent
:= Standard_Long_Long_Float
;
566 -- Only other possibility is user-defined enumeration type
569 if Discard_Names
(First_Subtype
(Ptyp
))
570 or else No
(Lit_Strings
(Root_Type
(Ptyp
)))
572 -- When pragma Discard_Names applies to the first subtype, build
573 -- (Pref'Pos (Expr))'Img.
576 Make_Attribute_Reference
(Loc
,
578 Make_Attribute_Reference
(Loc
,
580 Attribute_Name
=> Name_Pos
,
581 Expressions
=> New_List
(Expr
)),
584 Analyze_And_Resolve
(N
, Standard_String
);
588 -- Here for enumeration type case
590 Ttyp
:= Component_Type
(Etype
(Lit_Indexes
(Rtyp
)));
592 if Ttyp
= Standard_Integer_8
then
593 Imid
:= RE_Image_Enumeration_8
;
595 elsif Ttyp
= Standard_Integer_16
then
596 Imid
:= RE_Image_Enumeration_16
;
599 Imid
:= RE_Image_Enumeration_32
;
602 -- Apply a validity check, since it is a bit drastic to get a
603 -- completely junk image value for an invalid value.
605 if not Expr_Known_Valid
(Expr
) then
606 Insert_Valid_Check
(Expr
);
613 -- Build first argument for call
616 Arg_List
:= New_List
(
617 Make_Attribute_Reference
(Loc
,
618 Attribute_Name
=> Name_Pos
,
619 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
620 Expressions
=> New_List
(Expr
)));
623 Arg_List
:= New_List
(Convert_To
(Tent
, Expr
));
626 -- Append Snn, Pnn arguments
628 Append_To
(Arg_List
, New_Occurrence_Of
(Snn
, Loc
));
629 Append_To
(Arg_List
, New_Occurrence_Of
(Pnn
, Loc
));
631 -- Get entity of procedure to call
633 Proc_Ent
:= RTE
(Imid
);
635 -- If the procedure entity is empty, that means we have a case in
636 -- no run time mode where the operation is not allowed, and an
637 -- appropriate diagnostic has already been issued.
639 if No
(Proc_Ent
) then
643 -- Otherwise complete preparation of arguments for run-time call
645 -- Add extra arguments for Enumeration case
648 Append_To
(Arg_List
, New_Occurrence_Of
(Lit_Strings
(Rtyp
), Loc
));
650 Make_Attribute_Reference
(Loc
,
651 Prefix
=> New_Occurrence_Of
(Lit_Indexes
(Rtyp
), Loc
),
652 Attribute_Name
=> Name_Address
));
654 -- For floating-point types, append Digits argument
656 elsif Is_Floating_Point_Type
(Rtyp
) then
658 Make_Attribute_Reference
(Loc
,
659 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
660 Attribute_Name
=> Name_Digits
));
662 -- For ordinary fixed-point types, append Aft parameter
664 elsif Is_Ordinary_Fixed_Point_Type
(Rtyp
) then
666 Make_Attribute_Reference
(Loc
,
667 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
668 Attribute_Name
=> Name_Aft
));
670 if Has_Decimal_Small
(Rtyp
) then
671 Set_Conversion_OK
(First
(Arg_List
));
672 Set_Etype
(First
(Arg_List
), Tent
);
675 -- For decimal, append Scale and also set to do literal conversion
677 elsif Is_Decimal_Fixed_Point_Type
(Rtyp
) then
679 Make_Attribute_Reference
(Loc
,
680 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
681 Attribute_Name
=> Name_Scale
));
683 Set_Conversion_OK
(First
(Arg_List
));
684 Set_Etype
(First
(Arg_List
), Tent
);
686 -- For Wide_Character, append Ada 2005 indication
688 elsif Rtyp
= Standard_Wide_Character
then
691 (Boolean_Literals
(Ada_Version
>= Ada_2005
), Loc
));
694 -- Now append the procedure call to the insert list
697 Make_Procedure_Call_Statement
(Loc
,
698 Name
=> New_Occurrence_Of
(Proc_Ent
, Loc
),
699 Parameter_Associations
=> Arg_List
));
701 -- Insert declarations of Snn, Pnn, and the procedure call. We suppress
702 -- checks because we are sure that everything is in range at this stage.
704 Insert_Actions
(N
, Ins_List
, Suppress
=> All_Checks
);
706 -- Final step is to rewrite the expression as a slice and analyze,
707 -- again with no checks, since we are sure that everything is OK.
711 Prefix
=> New_Occurrence_Of
(Snn
, Loc
),
714 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
715 High_Bound
=> New_Occurrence_Of
(Pnn
, Loc
))));
717 Analyze_And_Resolve
(N
, Standard_String
, Suppress
=> All_Checks
);
718 end Expand_Image_Attribute
;
720 ----------------------------
721 -- Expand_Value_Attribute --
722 ----------------------------
724 -- For scalar types derived from Boolean, Character and integer types
725 -- in package Standard, typ'Value (X) expands into:
727 -- btyp (Value_xx (X))
729 -- where btyp is he base type of the prefix
731 -- For types whose root type is Character
734 -- For types whose root type is Wide_Character
735 -- xx = Wide_Character
737 -- For types whose root type is Wide_Wide_Character
738 -- xx = Wide_Wide_Character
740 -- For types whose root type is Boolean
743 -- For signed integer types with size <= Integer'Size
746 -- For other signed integer types
747 -- xx = Long_Long_Integer
749 -- For modular types with modulus <= System.Unsigned_Types.Unsigned
752 -- For other modular integer types
753 -- xx = Long_Long_Unsigned
755 -- For floating-point types and ordinary fixed-point types
758 -- For Wide_[Wide_]Character types, typ'Value (X) expands into:
760 -- btyp (Value_xx (X, EM))
762 -- where btyp is the base type of the prefix, and EM is the encoding method
764 -- For decimal types with size <= Integer'Size, typ'Value (X)
767 -- btyp?(Value_Decimal (X, typ'Scale));
769 -- For all other decimal types, typ'Value (X) expands into
771 -- btyp?(Value_Long_Long_Decimal (X, typ'Scale))
773 -- For enumeration types other than those derived from types Boolean,
774 -- Character, Wide_[Wide_]Character in Standard, typ'Value (X) expands to:
776 -- Enum'Val (Value_Enumeration_NN (typS, typI'Address, Num, X))
778 -- where typS and typI and the Lit_Strings and Lit_Indexes entities
779 -- from T's root type entity, and Num is Enum'Pos (Enum'Last). The
780 -- Value_Enumeration_NN function will search the tables looking for
781 -- X and return the position number in the table if found which is
782 -- used to provide the result of 'Value (using Enum'Val). If the
783 -- value is not found Constraint_Error is raised. The suffix _NN
784 -- depends on the element type of typI.
786 procedure Expand_Value_Attribute
(N
: Node_Id
) is
787 Loc
: constant Source_Ptr
:= Sloc
(N
);
788 Typ
: constant Entity_Id
:= Etype
(N
);
789 Btyp
: constant Entity_Id
:= Base_Type
(Typ
);
790 Rtyp
: constant Entity_Id
:= Root_Type
(Typ
);
791 Exprs
: constant List_Id
:= Expressions
(N
);
800 if Rtyp
= Standard_Character
then
801 Vid
:= RE_Value_Character
;
803 elsif Rtyp
= Standard_Boolean
then
804 Vid
:= RE_Value_Boolean
;
806 elsif Rtyp
= Standard_Wide_Character
then
807 Vid
:= RE_Value_Wide_Character
;
810 Make_Integer_Literal
(Loc
,
811 Intval
=> Int
(Wide_Character_Encoding_Method
)));
813 elsif Rtyp
= Standard_Wide_Wide_Character
then
814 Vid
:= RE_Value_Wide_Wide_Character
;
817 Make_Integer_Literal
(Loc
,
818 Intval
=> Int
(Wide_Character_Encoding_Method
)));
820 elsif Rtyp
= Base_Type
(Standard_Short_Short_Integer
)
821 or else Rtyp
= Base_Type
(Standard_Short_Integer
)
822 or else Rtyp
= Base_Type
(Standard_Integer
)
824 Vid
:= RE_Value_Integer
;
826 elsif Is_Signed_Integer_Type
(Rtyp
) then
827 Vid
:= RE_Value_Long_Long_Integer
;
829 elsif Is_Modular_Integer_Type
(Rtyp
) then
830 if Modulus
(Rtyp
) <= Modulus
(RTE
(RE_Unsigned
)) then
831 Vid
:= RE_Value_Unsigned
;
833 Vid
:= RE_Value_Long_Long_Unsigned
;
836 elsif Is_Decimal_Fixed_Point_Type
(Rtyp
) then
837 if UI_To_Int
(Esize
(Rtyp
)) <= Standard_Integer_Size
then
838 Vid
:= RE_Value_Decimal
;
840 Vid
:= RE_Value_Long_Long_Decimal
;
844 Make_Attribute_Reference
(Loc
,
845 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
846 Attribute_Name
=> Name_Scale
));
850 Make_Function_Call
(Loc
,
851 Name
=> New_Occurrence_Of
(RTE
(Vid
), Loc
),
852 Parameter_Associations
=> Args
)));
855 Analyze_And_Resolve
(N
, Btyp
);
858 elsif Is_Real_Type
(Rtyp
) then
859 Vid
:= RE_Value_Real
;
861 -- Only other possibility is user-defined enumeration type
864 pragma Assert
(Is_Enumeration_Type
(Rtyp
));
866 -- Case of pragma Discard_Names, transform the Value
867 -- attribute to Btyp'Val (Long_Long_Integer'Value (Args))
869 if Discard_Names
(First_Subtype
(Typ
))
870 or else No
(Lit_Strings
(Rtyp
))
873 Make_Attribute_Reference
(Loc
,
874 Prefix
=> New_Occurrence_Of
(Btyp
, Loc
),
875 Attribute_Name
=> Name_Val
,
876 Expressions
=> New_List
(
877 Make_Attribute_Reference
(Loc
,
879 New_Occurrence_Of
(Standard_Long_Long_Integer
, Loc
),
880 Attribute_Name
=> Name_Value
,
881 Expressions
=> Args
))));
883 Analyze_And_Resolve
(N
, Btyp
);
885 -- Here for normal case where we have enumeration tables, this
888 -- T'Val (Value_Enumeration_NN (typS, typI'Address, Num, X))
891 Ttyp
:= Component_Type
(Etype
(Lit_Indexes
(Rtyp
)));
893 if Ttyp
= Standard_Integer_8
then
894 Func
:= RE_Value_Enumeration_8
;
895 elsif Ttyp
= Standard_Integer_16
then
896 Func
:= RE_Value_Enumeration_16
;
898 Func
:= RE_Value_Enumeration_32
;
902 Make_Attribute_Reference
(Loc
,
903 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
),
904 Attribute_Name
=> Name_Pos
,
905 Expressions
=> New_List
(
906 Make_Attribute_Reference
(Loc
,
907 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
),
908 Attribute_Name
=> Name_Last
))));
911 Make_Attribute_Reference
(Loc
,
912 Prefix
=> New_Occurrence_Of
(Lit_Indexes
(Rtyp
), Loc
),
913 Attribute_Name
=> Name_Address
));
916 New_Occurrence_Of
(Lit_Strings
(Rtyp
), Loc
));
919 Make_Attribute_Reference
(Loc
,
920 Prefix
=> New_Occurrence_Of
(Typ
, Loc
),
921 Attribute_Name
=> Name_Val
,
922 Expressions
=> New_List
(
923 Make_Function_Call
(Loc
,
925 New_Occurrence_Of
(RTE
(Func
), Loc
),
926 Parameter_Associations
=> Args
))));
928 Analyze_And_Resolve
(N
, Btyp
);
934 -- Fall through for all cases except user-defined enumeration type
935 -- and decimal types, with Vid set to the Id of the entity for the
936 -- Value routine and Args set to the list of parameters for the call.
938 -- Compiling package Ada.Tags under No_Run_Time_Mode we disable the
939 -- expansion of the attribute into the function call statement to avoid
940 -- generating spurious errors caused by the use of Integer_Address'Value
941 -- in our implementation of Ada.Tags.Internal_Tag
943 -- Seems like a bit of a odd approach, there should be a better way ???
945 -- There is a better way, test RTE_Available ???
948 and then Rtyp
= RTE
(RE_Integer_Address
)
949 and then RTU_Loaded
(Ada_Tags
)
950 and then Cunit_Entity
(Current_Sem_Unit
)
951 = Body_Entity
(RTU_Entity
(Ada_Tags
))
954 Unchecked_Convert_To
(Rtyp
,
955 Make_Integer_Literal
(Loc
, Uint_0
)));
959 Make_Function_Call
(Loc
,
960 Name
=> New_Occurrence_Of
(RTE
(Vid
), Loc
),
961 Parameter_Associations
=> Args
)));
964 Analyze_And_Resolve
(N
, Btyp
);
965 end Expand_Value_Attribute
;
967 ---------------------------------
968 -- Expand_Wide_Image_Attribute --
969 ---------------------------------
971 -- We expand typ'Wide_Image (X) as follows. First we insert this code:
973 -- Rnn : Wide_String (1 .. rt'Wide_Width);
975 -- String_To_Wide_String
976 -- (typ'Image (Expr), Rnn, Lnn, Wide_Character_Encoding_Method);
978 -- where rt is the root type of the prefix type
980 -- Now we replace the Wide_Image reference by
984 -- This works in all cases because String_To_Wide_String converts any
985 -- wide character escape sequences resulting from the Image call to the
986 -- proper Wide_Character equivalent
988 -- not quite right for typ = Wide_Character ???
990 procedure Expand_Wide_Image_Attribute
(N
: Node_Id
) is
991 Loc
: constant Source_Ptr
:= Sloc
(N
);
992 Pref
: constant Entity_Id
:= Prefix
(N
);
993 Rnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
994 Lnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
998 if Is_Object_Image
(Pref
) then
999 Rewrite_Object_Image
(N
, Pref
, Name_Wide_Image
, Standard_Wide_String
);
1003 Rtyp
:= Root_Type
(Entity
(Pref
));
1005 Insert_Actions
(N
, New_List
(
1007 -- Rnn : Wide_String (1 .. base_typ'Width);
1009 Make_Object_Declaration
(Loc
,
1010 Defining_Identifier
=> Rnn
,
1011 Object_Definition
=>
1012 Make_Subtype_Indication
(Loc
,
1014 New_Occurrence_Of
(Standard_Wide_String
, Loc
),
1016 Make_Index_Or_Discriminant_Constraint
(Loc
,
1017 Constraints
=> New_List
(
1019 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
1021 Make_Attribute_Reference
(Loc
,
1022 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
),
1023 Attribute_Name
=> Name_Wide_Width
)))))),
1027 Make_Object_Declaration
(Loc
,
1028 Defining_Identifier
=> Lnn
,
1029 Object_Definition
=> New_Occurrence_Of
(Standard_Natural
, Loc
)),
1031 -- String_To_Wide_String
1032 -- (typ'Image (X), Rnn, Lnn, Wide_Character_Encoding_Method);
1034 Make_Procedure_Call_Statement
(Loc
,
1036 New_Occurrence_Of
(RTE
(RE_String_To_Wide_String
), Loc
),
1038 Parameter_Associations
=> New_List
(
1039 Make_Attribute_Reference
(Loc
,
1040 Prefix
=> Prefix
(N
),
1041 Attribute_Name
=> Name_Image
,
1042 Expressions
=> Expressions
(N
)),
1043 New_Occurrence_Of
(Rnn
, Loc
),
1044 New_Occurrence_Of
(Lnn
, Loc
),
1045 Make_Integer_Literal
(Loc
,
1046 Intval
=> Int
(Wide_Character_Encoding_Method
))))),
1048 -- Suppress checks because we know everything is properly in range
1050 Suppress
=> All_Checks
);
1052 -- Final step is to rewrite the expression as a slice and analyze,
1053 -- again with no checks, since we are sure that everything is OK.
1057 Prefix
=> New_Occurrence_Of
(Rnn
, Loc
),
1060 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
1061 High_Bound
=> New_Occurrence_Of
(Lnn
, Loc
))));
1063 Analyze_And_Resolve
(N
, Standard_Wide_String
, Suppress
=> All_Checks
);
1064 end Expand_Wide_Image_Attribute
;
1066 --------------------------------------
1067 -- Expand_Wide_Wide_Image_Attribute --
1068 --------------------------------------
1070 -- We expand typ'Wide_Wide_Image (X) as follows. First we insert this code:
1072 -- Rnn : Wide_Wide_String (1 .. rt'Wide_Wide_Width);
1074 -- String_To_Wide_Wide_String
1075 -- (typ'Image (Expr), Rnn, Lnn, Wide_Character_Encoding_Method);
1077 -- where rt is the root type of the prefix type
1079 -- Now we replace the Wide_Wide_Image reference by
1083 -- This works in all cases because String_To_Wide_Wide_String converts any
1084 -- wide character escape sequences resulting from the Image call to the
1085 -- proper Wide_Wide_Character equivalent
1087 -- not quite right for typ = Wide_Wide_Character ???
1089 procedure Expand_Wide_Wide_Image_Attribute
(N
: Node_Id
) is
1090 Loc
: constant Source_Ptr
:= Sloc
(N
);
1091 Pref
: constant Entity_Id
:= Prefix
(N
);
1092 Rnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
1093 Lnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'P');
1097 if Is_Object_Image
(Pref
) then
1098 Rewrite_Object_Image
1099 (N
, Pref
, Name_Wide_Wide_Image
, Standard_Wide_Wide_String
);
1103 Rtyp
:= Root_Type
(Entity
(Pref
));
1105 Insert_Actions
(N
, New_List
(
1107 -- Rnn : Wide_Wide_String (1 .. rt'Wide_Wide_Width);
1109 Make_Object_Declaration
(Loc
,
1110 Defining_Identifier
=> Rnn
,
1111 Object_Definition
=>
1112 Make_Subtype_Indication
(Loc
,
1114 New_Occurrence_Of
(Standard_Wide_Wide_String
, Loc
),
1116 Make_Index_Or_Discriminant_Constraint
(Loc
,
1117 Constraints
=> New_List
(
1119 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
1121 Make_Attribute_Reference
(Loc
,
1122 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
),
1123 Attribute_Name
=> Name_Wide_Wide_Width
)))))),
1127 Make_Object_Declaration
(Loc
,
1128 Defining_Identifier
=> Lnn
,
1129 Object_Definition
=> New_Occurrence_Of
(Standard_Natural
, Loc
)),
1131 -- String_To_Wide_Wide_String
1132 -- (typ'Image (X), Rnn, Lnn, Wide_Character_Encoding_Method);
1134 Make_Procedure_Call_Statement
(Loc
,
1136 New_Occurrence_Of
(RTE
(RE_String_To_Wide_Wide_String
), Loc
),
1138 Parameter_Associations
=> New_List
(
1139 Make_Attribute_Reference
(Loc
,
1140 Prefix
=> Prefix
(N
),
1141 Attribute_Name
=> Name_Image
,
1142 Expressions
=> Expressions
(N
)),
1143 New_Occurrence_Of
(Rnn
, Loc
),
1144 New_Occurrence_Of
(Lnn
, Loc
),
1145 Make_Integer_Literal
(Loc
,
1146 Intval
=> Int
(Wide_Character_Encoding_Method
))))),
1148 -- Suppress checks because we know everything is properly in range
1150 Suppress
=> All_Checks
);
1152 -- Final step is to rewrite the expression as a slice and analyze,
1153 -- again with no checks, since we are sure that everything is OK.
1157 Prefix
=> New_Occurrence_Of
(Rnn
, Loc
),
1160 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
1161 High_Bound
=> New_Occurrence_Of
(Lnn
, Loc
))));
1164 (N
, Standard_Wide_Wide_String
, Suppress
=> All_Checks
);
1165 end Expand_Wide_Wide_Image_Attribute
;
1167 ----------------------------
1168 -- Expand_Width_Attribute --
1169 ----------------------------
1171 -- The processing here also handles the case of Wide_[Wide_]Width. With the
1172 -- exceptions noted, the processing is identical
1174 -- For scalar types derived from Boolean, character and integer types
1175 -- in package Standard. Note that the Width attribute is computed at
1176 -- compile time for all cases except those involving non-static sub-
1177 -- types. For such subtypes, typ'[Wide_[Wide_]]Width expands into:
1179 -- Result_Type (xx (yy (Ptyp'First), yy (Ptyp'Last)))
1183 -- For types whose root type is Character
1184 -- xx = Width_Character
1187 -- For types whose root type is Wide_Character
1188 -- xx = Wide_Width_Character
1191 -- For types whose root type is Wide_Wide_Character
1192 -- xx = Wide_Wide_Width_Character
1195 -- For types whose root type is Boolean
1196 -- xx = Width_Boolean
1199 -- For signed integer types
1200 -- xx = Width_Long_Long_Integer
1201 -- yy = Long_Long_Integer
1203 -- For modular integer types
1204 -- xx = Width_Long_Long_Unsigned
1205 -- yy = Long_Long_Unsigned
1207 -- For types derived from Wide_Character, typ'Width expands into
1209 -- Result_Type (Width_Wide_Character (
1210 -- Wide_Character (typ'First),
1211 -- Wide_Character (typ'Last),
1213 -- and typ'Wide_Width expands into:
1215 -- Result_Type (Wide_Width_Wide_Character (
1216 -- Wide_Character (typ'First),
1217 -- Wide_Character (typ'Last));
1219 -- and typ'Wide_Wide_Width expands into
1221 -- Result_Type (Wide_Wide_Width_Wide_Character (
1222 -- Wide_Character (typ'First),
1223 -- Wide_Character (typ'Last));
1225 -- For types derived from Wide_Wide_Character, typ'Width expands into
1227 -- Result_Type (Width_Wide_Wide_Character (
1228 -- Wide_Wide_Character (typ'First),
1229 -- Wide_Wide_Character (typ'Last),
1231 -- and typ'Wide_Width expands into:
1233 -- Result_Type (Wide_Width_Wide_Wide_Character (
1234 -- Wide_Wide_Character (typ'First),
1235 -- Wide_Wide_Character (typ'Last));
1237 -- and typ'Wide_Wide_Width expands into
1239 -- Result_Type (Wide_Wide_Width_Wide_Wide_Char (
1240 -- Wide_Wide_Character (typ'First),
1241 -- Wide_Wide_Character (typ'Last));
1243 -- For real types, typ'Width and typ'Wide_[Wide_]Width expand into
1245 -- if Ptyp'First > Ptyp'Last then 0 else btyp'Width end if
1247 -- where btyp is the base type. This looks recursive but it isn't
1248 -- because the base type is always static, and hence the expression
1249 -- in the else is reduced to an integer literal.
1251 -- For user-defined enumeration types, typ'Width expands into
1253 -- Result_Type (Width_Enumeration_NN
1256 -- typ'Pos (typ'First),
1257 -- typ'Pos (Typ'Last)));
1259 -- and typ'Wide_Width expands into:
1261 -- Result_Type (Wide_Width_Enumeration_NN
1264 -- typ'Pos (typ'First),
1265 -- typ'Pos (Typ'Last))
1266 -- Wide_Character_Encoding_Method);
1268 -- and typ'Wide_Wide_Width expands into:
1270 -- Result_Type (Wide_Wide_Width_Enumeration_NN
1273 -- typ'Pos (typ'First),
1274 -- typ'Pos (Typ'Last))
1275 -- Wide_Character_Encoding_Method);
1277 -- where typS and typI are the enumeration image strings and indexes
1278 -- table, as described in Build_Enumeration_Image_Tables. NN is 8/16/32
1279 -- for depending on the element type for typI.
1281 -- Finally if Discard_Names is in effect for an enumeration type, then
1282 -- a special if expression is built that yields the space needed for the
1283 -- decimal representation of the largest pos value in the subtype. See
1284 -- code below for details.
1286 procedure Expand_Width_Attribute
(N
: Node_Id
; Attr
: Atype
:= Normal
) is
1287 Loc
: constant Source_Ptr
:= Sloc
(N
);
1288 Typ
: constant Entity_Id
:= Etype
(N
);
1289 Pref
: constant Node_Id
:= Prefix
(N
);
1290 Ptyp
: constant Entity_Id
:= Etype
(Pref
);
1291 Rtyp
: constant Entity_Id
:= Root_Type
(Ptyp
);
1298 -- Types derived from Standard.Boolean
1300 if Rtyp
= Standard_Boolean
then
1301 XX
:= RE_Width_Boolean
;
1304 -- Types derived from Standard.Character
1306 elsif Rtyp
= Standard_Character
then
1308 when Normal
=> XX
:= RE_Width_Character
;
1309 when Wide
=> XX
:= RE_Wide_Width_Character
;
1310 when Wide_Wide
=> XX
:= RE_Wide_Wide_Width_Character
;
1315 -- Types derived from Standard.Wide_Character
1317 elsif Rtyp
= Standard_Wide_Character
then
1319 when Normal
=> XX
:= RE_Width_Wide_Character
;
1320 when Wide
=> XX
:= RE_Wide_Width_Wide_Character
;
1321 when Wide_Wide
=> XX
:= RE_Wide_Wide_Width_Wide_Character
;
1326 -- Types derived from Standard.Wide_Wide_Character
1328 elsif Rtyp
= Standard_Wide_Wide_Character
then
1330 when Normal
=> XX
:= RE_Width_Wide_Wide_Character
;
1331 when Wide
=> XX
:= RE_Wide_Width_Wide_Wide_Character
;
1332 when Wide_Wide
=> XX
:= RE_Wide_Wide_Width_Wide_Wide_Char
;
1337 -- Signed integer types
1339 elsif Is_Signed_Integer_Type
(Rtyp
) then
1340 XX
:= RE_Width_Long_Long_Integer
;
1341 YY
:= Standard_Long_Long_Integer
;
1343 -- Modular integer types
1345 elsif Is_Modular_Integer_Type
(Rtyp
) then
1346 XX
:= RE_Width_Long_Long_Unsigned
;
1347 YY
:= RTE
(RE_Long_Long_Unsigned
);
1351 elsif Is_Real_Type
(Rtyp
) then
1353 Make_If_Expression
(Loc
,
1354 Expressions
=> New_List
(
1358 Make_Attribute_Reference
(Loc
,
1359 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1360 Attribute_Name
=> Name_First
),
1363 Make_Attribute_Reference
(Loc
,
1364 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1365 Attribute_Name
=> Name_Last
)),
1367 Make_Integer_Literal
(Loc
, 0),
1369 Make_Attribute_Reference
(Loc
,
1370 Prefix
=> New_Occurrence_Of
(Base_Type
(Ptyp
), Loc
),
1371 Attribute_Name
=> Name_Width
))));
1373 Analyze_And_Resolve
(N
, Typ
);
1376 -- User-defined enumeration types
1379 pragma Assert
(Is_Enumeration_Type
(Rtyp
));
1381 -- Whenever pragma Discard_Names is in effect, the value we need
1382 -- is the value needed to accommodate the largest integer pos value
1383 -- in the range of the subtype + 1 for the space at the start. We
1386 -- Tnn : constant Integer := Rtyp'Pos (Ptyp'Last)
1388 -- and replace the expression by
1390 -- (if Ptyp'Range_Length = 0 then 0
1391 -- else (if Tnn < 10 then 2
1392 -- else (if Tnn < 100 then 3
1396 -- where n is equal to Rtyp'Pos (Ptyp'Last) + 1
1398 -- Note: The above processing is in accordance with the intent of
1399 -- the RM, which is that Width should be related to the impl-defined
1400 -- behavior of Image. It is not clear what this means if Image is
1401 -- not defined (as in the configurable run-time case for GNAT) and
1402 -- gives an error at compile time.
1404 -- We choose in this case to just go ahead and implement Width the
1405 -- same way, returning what Image would have returned if it has been
1406 -- available in the configurable run-time library.
1408 if Discard_Names
(Rtyp
) then
1410 Tnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
1418 Make_Object_Declaration
(Loc
,
1419 Defining_Identifier
=> Tnn
,
1420 Constant_Present
=> True,
1421 Object_Definition
=>
1422 New_Occurrence_Of
(Standard_Integer
, Loc
),
1424 Make_Attribute_Reference
(Loc
,
1425 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
),
1426 Attribute_Name
=> Name_Pos
,
1427 Expressions
=> New_List
(
1429 Make_Attribute_Reference
(Loc
,
1430 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1431 Attribute_Name
=> Name_Last
))))));
1433 -- OK, now we need to build the if expression. First get the
1434 -- value of M, the largest possible value needed.
1437 (Enumeration_Pos
(Entity
(Type_High_Bound
(Rtyp
))));
1448 Cexpr
:= Make_Integer_Literal
(Loc
, K
);
1450 -- Wrap in inner if's until counted down to 2
1457 Make_If_Expression
(Loc
,
1458 Expressions
=> New_List
(
1460 Left_Opnd
=> New_Occurrence_Of
(Tnn
, Loc
),
1461 Right_Opnd
=> Make_Integer_Literal
(Loc
, M
)),
1462 Make_Integer_Literal
(Loc
, K
),
1466 -- Add initial comparison for null range and we are done, so
1467 -- rewrite the attribute occurrence with this expression.
1471 Make_If_Expression
(Loc
,
1472 Expressions
=> New_List
(
1475 Make_Attribute_Reference
(Loc
,
1476 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1477 Attribute_Name
=> Name_Range_Length
),
1478 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
1479 Make_Integer_Literal
(Loc
, 0),
1482 Analyze_And_Resolve
(N
, Typ
);
1487 -- Normal case, not Discard_Names
1489 Ttyp
:= Component_Type
(Etype
(Lit_Indexes
(Rtyp
)));
1493 if Ttyp
= Standard_Integer_8
then
1494 XX
:= RE_Width_Enumeration_8
;
1495 elsif Ttyp
= Standard_Integer_16
then
1496 XX
:= RE_Width_Enumeration_16
;
1498 XX
:= RE_Width_Enumeration_32
;
1502 if Ttyp
= Standard_Integer_8
then
1503 XX
:= RE_Wide_Width_Enumeration_8
;
1504 elsif Ttyp
= Standard_Integer_16
then
1505 XX
:= RE_Wide_Width_Enumeration_16
;
1507 XX
:= RE_Wide_Width_Enumeration_32
;
1511 if Ttyp
= Standard_Integer_8
then
1512 XX
:= RE_Wide_Wide_Width_Enumeration_8
;
1513 elsif Ttyp
= Standard_Integer_16
then
1514 XX
:= RE_Wide_Wide_Width_Enumeration_16
;
1516 XX
:= RE_Wide_Wide_Width_Enumeration_32
;
1522 New_Occurrence_Of
(Lit_Strings
(Rtyp
), Loc
),
1524 Make_Attribute_Reference
(Loc
,
1525 Prefix
=> New_Occurrence_Of
(Lit_Indexes
(Rtyp
), Loc
),
1526 Attribute_Name
=> Name_Address
),
1528 Make_Attribute_Reference
(Loc
,
1529 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1530 Attribute_Name
=> Name_Pos
,
1532 Expressions
=> New_List
(
1533 Make_Attribute_Reference
(Loc
,
1534 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1535 Attribute_Name
=> Name_First
))),
1537 Make_Attribute_Reference
(Loc
,
1538 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1539 Attribute_Name
=> Name_Pos
,
1541 Expressions
=> New_List
(
1542 Make_Attribute_Reference
(Loc
,
1543 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1544 Attribute_Name
=> Name_Last
))));
1548 Make_Function_Call
(Loc
,
1549 Name
=> New_Occurrence_Of
(RTE
(XX
), Loc
),
1550 Parameter_Associations
=> Arglist
)));
1552 Analyze_And_Resolve
(N
, Typ
);
1556 -- If we fall through XX and YY are set
1558 Arglist
:= New_List
(
1560 Make_Attribute_Reference
(Loc
,
1561 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1562 Attribute_Name
=> Name_First
)),
1565 Make_Attribute_Reference
(Loc
,
1566 Prefix
=> New_Occurrence_Of
(Ptyp
, Loc
),
1567 Attribute_Name
=> Name_Last
)));
1571 Make_Function_Call
(Loc
,
1572 Name
=> New_Occurrence_Of
(RTE
(XX
), Loc
),
1573 Parameter_Associations
=> Arglist
)));
1575 Analyze_And_Resolve
(N
, Typ
);
1576 end Expand_Width_Attribute
;
1578 -----------------------
1579 -- Has_Decimal_Small --
1580 -----------------------
1582 function Has_Decimal_Small
(E
: Entity_Id
) return Boolean is
1584 return Is_Decimal_Fixed_Point_Type
(E
)
1586 (Is_Ordinary_Fixed_Point_Type
(E
)
1587 and then Ureal_10
**Aft_Value
(E
) * Small_Value
(E
) = Ureal_1
);
1588 end Has_Decimal_Small
;
1590 --------------------------
1591 -- Rewrite_Object_Image --
1592 --------------------------
1594 procedure Rewrite_Object_Image
1597 Attr_Name
: Name_Id
;
1598 Str_Typ
: Entity_Id
)
1602 Make_Attribute_Reference
(Sloc
(N
),
1603 Prefix
=> New_Occurrence_Of
(Etype
(Pref
), Sloc
(N
)),
1604 Attribute_Name
=> Attr_Name
,
1605 Expressions
=> New_List
(Relocate_Node
(Pref
))));
1607 Analyze_And_Resolve
(N
, Str_Typ
);
1608 end Rewrite_Object_Image
;