1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                                T Y P E S                                 --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2020, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
25
26--  This package contains host independent type definitions which are used
27--  in more than one unit in the compiler. They are gathered here for easy
28--  reference, although in some cases the full description is found in the
29--  relevant module which implements the definition. The main reason that they
30--  are not in their "natural" specs is that this would cause a lot of inter-
31--  spec dependencies, and in particular some awkward circular dependencies
32--  would have to be dealt with.
33
34--  WARNING: There is a C version of this package. Any changes to this source
35--  file must be properly reflected in the C header file types.h
36
37--  Note: the declarations in this package reflect an expectation that the host
38--  machine has an efficient integer base type with a range at least 32 bits
39--  2s-complement. If there are any machines for which this is not a correct
40--  assumption, a significant number of changes will be required.
41
42with System;
43with Unchecked_Conversion;
44with Unchecked_Deallocation;
45
46package Types is
47   pragma Preelaborate;
48
49   -------------------------------
50   -- General Use Integer Types --
51   -------------------------------
52
53   type Int is range -2 ** 31 .. +2 ** 31 - 1;
54   --  Signed 32-bit integer
55
56   subtype Nat is Int range 0 .. Int'Last;
57   --  Non-negative Int values
58
59   subtype Pos is Int range 1 .. Int'Last;
60   --  Positive Int values
61
62   type Word is mod 2 ** 32;
63   --  Unsigned 32-bit integer
64
65   type Short is range -32768 .. +32767;
66   for Short'Size use 16;
67   --  16-bit signed integer
68
69   type Byte is mod 2 ** 8;
70   for Byte'Size use 8;
71   --  8-bit unsigned integer
72
73   type size_t is mod 2 ** Standard'Address_Size;
74   --  Memory size value, for use in calls to C routines
75
76   --------------------------------------
77   -- 8-Bit Character and String Types --
78   --------------------------------------
79
80   --  We use Standard.Character and Standard.String freely, since we are
81   --  compiling ourselves, and we properly implement the required 8-bit
82   --  character code as required in Ada 95. This section defines a few
83   --  general use constants and subtypes.
84
85   EOF : constant Character := ASCII.SUB;
86   --  The character SUB (16#1A#) is used in DOS and other systems derived
87   --  from DOS (XP, NT etc) to signal the end of a text file. Internally
88   --  all source files are ended by an EOF character, even on Unix systems.
89   --  An EOF character acts as the end of file only as the last character
90   --  of a source buffer, in any other position, it is treated as a blank
91   --  if it appears between tokens, and as an illegal character otherwise.
92   --  This makes life easier dealing with files that originated from DOS,
93   --  including concatenated files with interspersed EOF characters.
94
95   subtype Graphic_Character is Character range ' ' .. '~';
96   --  Graphic characters, as defined in ARM
97
98   subtype Line_Terminator is Character range ASCII.LF .. ASCII.CR;
99   --  Line terminator characters (LF, VT, FF, CR). For further details, see
100   --  the extensive discussion of line termination in the Sinput spec.
101
102   subtype Upper_Half_Character is
103     Character range Character'Val (16#80#) .. Character'Val (16#FF#);
104   --  8-bit Characters with the upper bit set
105
106   type Character_Ptr    is access all Character;
107   type String_Ptr       is access all String;
108   type String_Ptr_Const is access constant String;
109   --  Standard character and string pointers
110
111   procedure Free is new Unchecked_Deallocation (String, String_Ptr);
112   --  Procedure for freeing dynamically allocated String values
113
114   subtype Big_String is String (Positive);
115   type Big_String_Ptr is access all Big_String;
116   --  Virtual type for handling imported big strings. Note that we should
117   --  never have any allocators for this type, but we don't give a storage
118   --  size of zero, since there are legitimate deallocations going on.
119
120   function To_Big_String_Ptr is
121     new Unchecked_Conversion (System.Address, Big_String_Ptr);
122   --  Used to obtain Big_String_Ptr values from external addresses
123
124   subtype Word_Hex_String is String (1 .. 8);
125   --  Type used to represent Word value as 8 hex digits, with lower case
126   --  letters for the alphabetic cases.
127
128   function Get_Hex_String (W : Word) return Word_Hex_String;
129   --  Convert word value to 8-character hex string
130
131   -----------------------------------------
132   -- Types Used for Text Buffer Handling --
133   -----------------------------------------
134
135   --  We cannot use type String for text buffers, since we must use the
136   --  standard 32-bit integer as an index value, since we count on all index
137   --  values being the same size.
138
139   type Text_Ptr is new Int;
140   --  Type used for subscripts in text buffer
141
142   type Text_Buffer is array (Text_Ptr range <>) of Character;
143   --  Text buffer used to hold source file or library information file
144
145   type Text_Buffer_Ptr is access all Text_Buffer;
146   --  Text buffers for input files are allocated dynamically and this type
147   --  is used to reference these text buffers.
148
149   procedure Free is new Unchecked_Deallocation (Text_Buffer, Text_Buffer_Ptr);
150   --  Procedure for freeing dynamically allocated text buffers
151
152   ------------------------------------------
153   -- Types Used for Source Input Handling --
154   ------------------------------------------
155
156   type Logical_Line_Number is range 0 .. Int'Last;
157   for Logical_Line_Number'Size use 32;
158   --  Line number type, used for storing logical line numbers (i.e. line
159   --  numbers that include effects of any Source_Reference pragmas in the
160   --  source file). The value zero indicates a line containing a source
161   --  reference pragma.
162
163   No_Line_Number : constant Logical_Line_Number := 0;
164   --  Special value used to indicate no line number
165
166   type Physical_Line_Number is range 1 .. Int'Last;
167   for Physical_Line_Number'Size use 32;
168   --  Line number type, used for storing physical line numbers (i.e. line
169   --  numbers in the physical file being compiled, unaffected by the presence
170   --  of source reference pragmas).
171
172   type Column_Number is range 0 .. 32767;
173   for Column_Number'Size use 16;
174   --  Column number (assume that 2**15 - 1 is large enough). The range for
175   --  this type is used to compute Hostparm.Max_Line_Length. See also the
176   --  processing for -gnatyM in Stylesw).
177
178   No_Column_Number : constant Column_Number := 0;
179   --  Special value used to indicate no column number
180
181   Source_Align : constant := 2 ** 12;
182   --  Alignment requirement for source buffers (by keeping source buffers
183   --  aligned, we can optimize the implementation of Get_Source_File_Index.
184   --  See this routine in Sinput for details.
185
186   subtype Source_Buffer is Text_Buffer;
187   --  Type used to store text of a source file. The buffer for the main
188   --  source (the source specified on the command line) has a lower bound
189   --  starting at zero. Subsequent subsidiary sources have lower bounds
190   --  which are one greater than the previous upper bound, rounded up to
191   --  a multiple of Source_Align.
192
193   type Source_Buffer_Ptr_Var is access all Source_Buffer;
194   type Source_Buffer_Ptr is access constant Source_Buffer;
195   --  Pointer to source buffer. Source_Buffer_Ptr_Var is used for allocation
196   --  and deallocation; Source_Buffer_Ptr is used for all other uses of source
197   --  buffers.
198
199   function Null_Source_Buffer_Ptr (X : Source_Buffer_Ptr) return Boolean;
200   --  True if X = null
201
202   function Source_Buffer_Ptr_Equal (X, Y : Source_Buffer_Ptr) return Boolean
203     renames "=";
204   --  Squirrel away the predefined "=", for use in Null_Source_Buffer_Ptr.
205   --  Do not call this elsewhere.
206
207   function "=" (X, Y : Source_Buffer_Ptr) return Boolean is abstract;
208   --  Make "=" abstract. Note that this makes "/=" abstract as well. This is a
209   --  vestige of the zero-origin array indexing we used to use, where "=" is
210   --  always wrong (including the one in Null_Source_Buffer_Ptr). We keep this
211   --  just because we never need to compare Source_Buffer_Ptrs other than to
212   --  null.
213
214   subtype Source_Ptr is Text_Ptr;
215   --  Type used to represent a source location, which is a subscript of a
216   --  character in the source buffer. As noted above, different source buffers
217   --  have different ranges, so it is possible to tell from a Source_Ptr value
218   --  which source it refers to. Note that negative numbers are allowed to
219   --  accommodate the following special values.
220
221   No_Location : constant Source_Ptr := -1;
222   --  Value used to indicate no source position set in a node. A test for a
223   --  Source_Ptr value being > No_Location is the approved way to test for a
224   --  standard value that does not include No_Location or any of the following
225   --  special definitions. One important use of No_Location is to label
226   --  generated nodes that we don't want the debugger to see in normal mode
227   --  (very often we conditionalize so that we set No_Location in normal mode
228   --  and the corresponding source line in -gnatD mode).
229
230   Standard_Location : constant Source_Ptr := -2;
231   --  Used for all nodes in the representation of package Standard other than
232   --  nodes representing the contents of Standard.ASCII. Note that testing for
233   --  a value being <= Standard_Location tests for both Standard_Location and
234   --  for Standard_ASCII_Location.
235
236   Standard_ASCII_Location : constant Source_Ptr := -3;
237   --  Used for all nodes in the presentation of package Standard.ASCII
238
239   System_Location : constant Source_Ptr := -4;
240   --  Used to identify locations of pragmas scanned by Targparm, where we know
241   --  the location is in System, but we don't know exactly what line.
242
243   First_Source_Ptr : constant Source_Ptr := 0;
244   --  Starting source pointer index value for first source program
245
246   -------------------------------------
247   -- Range Definitions for Tree Data --
248   -------------------------------------
249
250   --  The tree has fields that can hold any of the following types:
251
252   --    Pointers to other tree nodes (type Node_Id)
253   --    List pointers (type List_Id)
254   --    Element list pointers (type Elist_Id)
255   --    Names (type Name_Id)
256   --    Strings (type String_Id)
257   --    Universal integers (type Uint)
258   --    Universal reals (type Ureal)
259
260   --  These types are represented as integer indices into various tables.
261   --  However, they should be treated as private, except in a few documented
262   --  cases. In particular it is usually inappropriate to perform arithmetic
263   --  operations using these types. One exception is in computing hash
264   --  functions of these types.
265
266   --  In most contexts, the strongly typed interface determines which of these
267   --  types is present. However, there are some situations (involving untyped
268   --  traversals of the tree), where it is convenient to be easily able to
269   --  distinguish these values. The underlying representation in all cases is
270   --  an integer type Union_Id, and we ensure that the range of the various
271   --  possible values for each of the above types is disjoint (except that
272   --  List_Id and Node_Id overlap at Empty) so that this distinction is
273   --  possible.
274
275   --  Note: it is also helpful for debugging purposes to make these ranges
276   --  distinct. If a bug leads to misidentification of a value, then it will
277   --  typically result in an out of range value and a Constraint_Error.
278
279   --  The range of Node_Id is most of the nonnegative integers. The other
280   --  ranges are negative. Uint has a very large range, because a substantial
281   --  part of this range is used to store direct values; see Uintp for
282   --  details. The other types have 100 million values, which should be
283   --  plenty.
284
285   type Union_Id is new Int;
286   --  The type in the tree for a union of possible ID values
287
288   --  Following are the Low and High bounds of the various ranges.
289
290   List_Low_Bound : constant := -099_999_999;
291   --  The List_Id values are subscripts into an array of list headers which
292   --  has List_Low_Bound as its lower bound.
293
294   List_High_Bound : constant := 0;
295   --  Maximum List_Id subscript value. The ranges of List_Id and Node_Id
296   --  overlap by one element (with value zero), which is used both for the
297   --  Empty node, and for No_List. The fact that the same value is used is
298   --  convenient because it means that the default value of Empty applies to
299   --  both nodes and lists, and also is more efficient to test for.
300
301   Node_Low_Bound : constant := 0;
302   --  The tree Id values start at zero, because we use zero for Empty (to
303   --  allow a zero test for Empty).
304
305   Node_High_Bound : constant :=
306     (if Standard'Address_Size = 32 then 299_999_999 else 1_999_999_999);
307
308   Elist_Low_Bound : constant := -199_999_999;
309   --  The Elist_Id values are subscripts into an array of elist headers which
310   --  has Elist_Low_Bound as its lower bound.
311
312   Elist_High_Bound : constant := -100_000_000;
313
314   Elmt_Low_Bound : constant := -299_999_999;
315   --  Low bound of element Id values. The use of these values is internal to
316   --  the Elists package, but the definition of the range is included here
317   --  since it must be disjoint from other Id values. The Elmt_Id values are
318   --  subscripts into an array of list elements which has this as lower bound.
319
320   Elmt_High_Bound : constant := -200_000_000;
321
322   Names_Low_Bound : constant := -399_999_999;
323
324   Names_High_Bound : constant := -300_000_000;
325
326   Strings_Low_Bound : constant := -499_999_999;
327
328   Strings_High_Bound : constant := -400_000_000;
329
330   Ureal_Low_Bound : constant := -599_999_999;
331
332   Ureal_High_Bound : constant := -500_000_000;
333
334   Uint_Low_Bound : constant := -2_100_000_000;
335   --  Low bound for Uint values
336
337   Uint_Table_Start : constant := -699_999_999;
338   --  Location where table entries for universal integers start (see
339   --  Uintp spec for details of the representation of Uint values).
340
341   Uint_High_Bound : constant := -600_000_000;
342
343   --  The following subtype definitions are used to provide convenient names
344   --  for membership tests on Int values to see what data type range they
345   --  lie in. Such tests appear only in the lowest level packages.
346
347   subtype List_Range      is Union_Id
348     range List_Low_Bound    .. List_High_Bound;
349
350   subtype Node_Range      is Union_Id
351     range Node_Low_Bound    .. Node_High_Bound;
352
353   subtype Elist_Range     is Union_Id
354     range Elist_Low_Bound   .. Elist_High_Bound;
355
356   subtype Elmt_Range      is Union_Id
357     range Elmt_Low_Bound    .. Elmt_High_Bound;
358
359   subtype Names_Range     is Union_Id
360     range Names_Low_Bound   .. Names_High_Bound;
361
362   subtype Strings_Range   is Union_Id
363     range Strings_Low_Bound .. Strings_High_Bound;
364
365   subtype Uint_Range      is Union_Id
366     range Uint_Low_Bound    .. Uint_High_Bound;
367
368   subtype Ureal_Range     is Union_Id
369     range Ureal_Low_Bound   .. Ureal_High_Bound;
370
371   -----------------------------
372   -- Types for Atree Package --
373   -----------------------------
374
375   --  Node_Id values are used to identify nodes in the tree. They are
376   --  subscripts into the Nodes table declared in package Atree. Note that
377   --  the special values Empty and Error are subscripts into this table.
378   --  See package Atree for further details.
379
380   type Node_Id is range Node_Low_Bound .. Node_High_Bound;
381   --  Type used to identify nodes in the tree
382
383   subtype Entity_Id is Node_Id;
384   --  A synonym for node types, used in the Einfo package to refer to nodes
385   --  that are entities (i.e. nodes with an Nkind of N_Defining_xxx). All such
386   --  nodes are extended nodes and these are the only extended nodes, so that
387   --  in practice entity and extended nodes are synonymous.
388
389   subtype Node_Or_Entity_Id is Node_Id;
390   --  A synonym for node types, used in cases where a given value may be used
391   --  to represent either a node or an entity. We like to minimize such uses
392   --  for obvious reasons of logical type consistency, but where such uses
393   --  occur, they should be documented by use of this type.
394
395   Empty : constant Node_Id := Node_Low_Bound;
396   --  Used to indicate null node. A node is actually allocated with this
397   --  Id value, so that Nkind (Empty) = N_Empty. Note that Node_Low_Bound
398   --  is zero, so Empty = No_List = zero.
399
400   Empty_List_Or_Node : constant := 0;
401   --  This constant is used in situations (e.g. initializing empty fields)
402   --  where the value set will be used to represent either an empty node or
403   --  a non-existent list, depending on the context.
404
405   Error : constant Node_Id := Node_Low_Bound + 1;
406   --  Used to indicate an error in the source program. A node is actually
407   --  allocated with this Id value, so that Nkind (Error) = N_Error.
408
409   Empty_Or_Error : constant Node_Id := Error;
410   --  Since Empty and Error are the first two Node_Id values, the test for
411   --  N <= Empty_Or_Error tests to see if N is Empty or Error. This definition
412   --  provides convenient self-documentation for such tests.
413
414   First_Node_Id  : constant Node_Id := Node_Low_Bound;
415   --  Subscript of first allocated node. Note that Empty and Error are both
416   --  allocated nodes, whose Nkind fields can be accessed without error.
417
418   ------------------------------
419   -- Types for Nlists Package --
420   ------------------------------
421
422   --  List_Id values are used to identify node lists stored in the tree, so
423   --  that each node can be on at most one such list (see package Nlists for
424   --  further details). Note that the special value Error_List is a subscript
425   --  in this table, but the value No_List is *not* a valid subscript, and any
426   --  attempt to apply list operations to No_List will cause a (detected)
427   --  error.
428
429   type List_Id is range List_Low_Bound .. List_High_Bound;
430   --  Type used to identify a node list
431
432   No_List : constant List_Id := List_High_Bound;
433   --  Used to indicate absence of a list. Note that the value is zero, which
434   --  is the same as Empty, which is helpful in initializing nodes where a
435   --  value of zero can represent either an empty node or an empty list.
436
437   Error_List : constant List_Id := List_Low_Bound;
438   --  Used to indicate that there was an error in the source program in a
439   --  context which would normally require a list. This node appears to be
440   --  an empty list to the list operations (a null list is actually allocated
441   --  which has this Id value).
442
443   First_List_Id : constant List_Id := Error_List;
444   --  Subscript of first allocated list header
445
446   ------------------------------
447   -- Types for Elists Package --
448   ------------------------------
449
450   --  Element list Id values are used to identify element lists stored outside
451   --  of the tree, allowing nodes to be members of more than one such list
452   --  (see package Elists for further details).
453
454   type Elist_Id is range Elist_Low_Bound .. Elist_High_Bound;
455   --  Type used to identify an element list (Elist header table subscript)
456
457   No_Elist : constant Elist_Id := Elist_Low_Bound;
458   --  Used to indicate absence of an element list. Note that this is not an
459   --  actual Elist header, so element list operations on this value are not
460   --  valid.
461
462   First_Elist_Id : constant Elist_Id := No_Elist + 1;
463   --  Subscript of first allocated Elist header
464
465   --  Element Id values are used to identify individual elements of an element
466   --  list (see package Elists for further details).
467
468   type Elmt_Id is range Elmt_Low_Bound .. Elmt_High_Bound;
469   --  Type used to identify an element list
470
471   No_Elmt : constant Elmt_Id := Elmt_Low_Bound;
472   --  Used to represent empty element
473
474   First_Elmt_Id : constant Elmt_Id := No_Elmt + 1;
475   --  Subscript of first allocated Elmt table entry
476
477   -------------------------------
478   -- Types for Stringt Package --
479   -------------------------------
480
481   --  String_Id values are used to identify entries in the strings table. They
482   --  are subscripts into the Strings table defined in package Stringt.
483
484   type String_Id is range Strings_Low_Bound .. Strings_High_Bound;
485   --  Type used to identify entries in the strings table
486
487   No_String : constant String_Id := Strings_Low_Bound;
488   --  Used to indicate missing string Id. Note that the value zero is used
489   --  to indicate a missing data value for all the Int types in this section.
490
491   First_String_Id : constant String_Id := No_String + 1;
492   --  First subscript allocated in string table
493
494   -------------------------
495   -- Character Code Type --
496   -------------------------
497
498   --  The type Char is used for character data internally in the compiler, but
499   --  character codes in the source are represented by the Char_Code type.
500   --  Each character literal in the source is interpreted as being one of the
501   --  16#7FFF_FFFF# possible Wide_Wide_Character codes, and a unique Integer
502   --  value is assigned, corresponding to the UTF-32 value, which also
503   --  corresponds to the Pos value in the Wide_Wide_Character type, and also
504   --  corresponds to the Pos value in the Wide_Character and Character types
505   --  for values that are in appropriate range. String literals are similarly
506   --  interpreted as a sequence of such codes.
507
508   type Char_Code_Base is mod 2 ** 32;
509   for Char_Code_Base'Size use 32;
510
511   subtype Char_Code is Char_Code_Base range 0 .. 16#7FFF_FFFF#;
512   for Char_Code'Value_Size use 32;
513   for Char_Code'Object_Size use 32;
514
515   function Get_Char_Code (C : Character) return Char_Code;
516   pragma Inline (Get_Char_Code);
517   --  Function to obtain internal character code from source character. For
518   --  the moment, the internal character code is simply the Pos value of the
519   --  input source character, but we provide this interface for possible
520   --  later support of alternative character sets.
521
522   function In_Character_Range (C : Char_Code) return Boolean;
523   pragma Inline (In_Character_Range);
524   --  Determines if the given character code is in range of type Character,
525   --  and if so, returns True. If not, returns False.
526
527   function In_Wide_Character_Range (C : Char_Code) return Boolean;
528   pragma Inline (In_Wide_Character_Range);
529   --  Determines if the given character code is in range of the type
530   --  Wide_Character, and if so, returns True. If not, returns False.
531
532   function Get_Character (C : Char_Code) return Character;
533   pragma Inline (Get_Character);
534   --  For a character C that is in Character range (see above function), this
535   --  function returns the corresponding Character value. It is an error to
536   --  call Get_Character if C is not in Character range.
537
538   function Get_Wide_Character (C : Char_Code) return Wide_Character;
539   --  For a character C that is in Wide_Character range (see above function),
540   --  this function returns the corresponding Wide_Character value. It is an
541   --  error to call Get_Wide_Character if C is not in Wide_Character range.
542
543   ---------------------------------------
544   -- Types used for Library Management --
545   ---------------------------------------
546
547   type Unit_Number_Type is new Int range -1 .. Int'Last;
548   --  Unit number. The main source is unit 0, and subsidiary sources have
549   --  non-zero numbers starting with 1. Unit numbers are used to index the
550   --  Units table in package Lib.
551
552   Main_Unit : constant Unit_Number_Type := 0;
553   --  Unit number value for main unit
554
555   No_Unit : constant Unit_Number_Type := -1;
556   --  Special value used to signal no unit
557
558   type Source_File_Index is new Int range -1 .. Int'Last;
559   --  Type used to index the source file table (see package Sinput)
560
561   No_Source_File : constant Source_File_Index := 0;
562   --  Value used to indicate no source file present
563
564   No_Access_To_Source_File : constant Source_File_Index := -1;
565   --  Value used to indicate a source file is present but unreadable
566
567   -----------------------------------
568   -- Representation of Time Stamps --
569   -----------------------------------
570
571   --  All compiled units are marked with a time stamp which is derived from
572   --  the source file (we assume that the host system has the concept of a
573   --  file time stamp which is modified when a file is modified). These
574   --  time stamps are used to ensure consistency of the set of units that
575   --  constitutes a library. Time stamps are 14-character strings with
576   --  with the following format:
577
578   --     YYYYMMDDHHMMSS
579
580   --       YYYY   year
581   --       MM     month (2 digits 01-12)
582   --       DD     day (2 digits 01-31)
583   --       HH     hour (2 digits 00-23)
584   --       MM     minutes (2 digits 00-59)
585   --       SS     seconds (2 digits 00-59)
586
587   --  In the case of Unix systems (and other systems which keep the time in
588   --  GMT), the time stamp is the GMT time of the file, not the local time.
589   --  This solves problems in using libraries across networks with clients
590   --  spread across multiple time-zones.
591
592   Time_Stamp_Length : constant := 14;
593   --  Length of time stamp value
594
595   subtype Time_Stamp_Index is Natural range 1 .. Time_Stamp_Length;
596   type Time_Stamp_Type is new String (Time_Stamp_Index);
597   --  Type used to represent time stamp
598
599   Empty_Time_Stamp : constant Time_Stamp_Type := (others => ' ');
600   --  Value representing an empty or missing time stamp. Looks less than any
601   --  real time stamp if two time stamps are compared. Note that although this
602   --  is not private, clients should not rely on the exact way in which this
603   --  string is represented, and instead should use the subprograms below.
604
605   Dummy_Time_Stamp : constant Time_Stamp_Type := (others => '0');
606   --  This is used for dummy time stamp values used in the D lines for
607   --  non-existent files, and is intended to be an impossible value.
608
609   function "="  (Left, Right : Time_Stamp_Type) return Boolean;
610   function "<=" (Left, Right : Time_Stamp_Type) return Boolean;
611   function ">=" (Left, Right : Time_Stamp_Type) return Boolean;
612   function "<"  (Left, Right : Time_Stamp_Type) return Boolean;
613   function ">"  (Left, Right : Time_Stamp_Type) return Boolean;
614   --  Comparison functions on time stamps. Note that two time stamps are
615   --  defined as being equal if they have the same day/month/year and the
616   --  hour/minutes/seconds values are within 2 seconds of one another. This
617   --  deals with rounding effects in library file time stamps caused by
618   --  copying operations during installation. We have particularly noticed
619   --  that WinNT seems susceptible to such changes.
620   --
621   --  Note: the Empty_Time_Stamp value looks equal to itself, and less than
622   --  any non-empty time stamp value.
623
624   procedure Split_Time_Stamp
625     (TS      : Time_Stamp_Type;
626      Year    : out Nat;
627      Month   : out Nat;
628      Day     : out Nat;
629      Hour    : out Nat;
630      Minutes : out Nat;
631      Seconds : out Nat);
632   --  Given a time stamp, decompose it into its components
633
634   procedure Make_Time_Stamp
635     (Year    : Nat;
636      Month   : Nat;
637      Day     : Nat;
638      Hour    : Nat;
639      Minutes : Nat;
640      Seconds : Nat;
641      TS      : out Time_Stamp_Type);
642   --  Given the components of a time stamp, initialize the value
643
644   -------------------------------------
645   -- Types used for Check Management --
646   -------------------------------------
647
648   type Check_Id is new Nat;
649   --  Type used to represent a check id
650
651   No_Check_Id : constant := 0;
652   --  Check_Id value used to indicate no check
653
654   Access_Check               : constant :=  1;
655   Accessibility_Check        : constant :=  2;
656   Alignment_Check            : constant :=  3;
657   Allocation_Check           : constant :=  4;
658   Atomic_Synchronization     : constant :=  5;
659   Characters_Assertion_Check : constant :=  6;
660   Containers_Assertion_Check : constant :=  7;
661   Discriminant_Check         : constant :=  8;
662   Division_Check             : constant :=  9;
663   Duplicated_Tag_Check       : constant := 10;
664   Elaboration_Check          : constant := 11;
665   Index_Check                : constant := 12;
666   Interfaces_Assertion_Check : constant := 13;
667   IO_Assertion_Check         : constant := 14;
668   Length_Check               : constant := 15;
669   Numerics_Assertion_Check   : constant := 16;
670   Overflow_Check             : constant := 17;
671   Predicate_Check            : constant := 18;
672   Program_Error_Check        : constant := 19;
673   Range_Check                : constant := 20;
674   Storage_Check              : constant := 21;
675   Strings_Assertion_Check    : constant := 22;
676   System_Assertion_Check     : constant := 23;
677   Tag_Check                  : constant := 24;
678   Validity_Check             : constant := 25;
679   Container_Checks           : constant := 26;
680   Tampering_Check            : constant := 27;
681   Tasking_Check              : constant := 28;
682   --  Values used to represent individual predefined checks (including the
683   --  setting of Atomic_Synchronization, which is implemented internally using
684   --  a "check" whose name is Atomic_Synchronization).
685
686   All_Checks : constant := 29;
687   --  Value used to represent All_Checks value
688
689   subtype Predefined_Check_Id is Check_Id range 1 .. All_Checks;
690   --  Subtype for predefined checks, including All_Checks
691
692   --  The following array contains an entry for each recognized check name
693   --  for pragma Suppress. It is used to represent current settings of scope
694   --  based suppress actions from pragma Suppress or command line settings.
695
696   --  Note: when Suppress_Array (All_Checks) is True, then generally all other
697   --  specific check entries are set True, except for the Elaboration_Check
698   --  entry which is set only if an explicit Suppress for this check is given.
699   --  The reason for this non-uniformity is that we do not want All_Checks to
700   --  suppress elaboration checking when using the static elaboration model.
701   --  We recognize only an explicit suppress of Elaboration_Check as a signal
702   --  that the static elaboration checking should skip a compile time check.
703
704   type Suppress_Array is array (Predefined_Check_Id) of Boolean;
705   pragma Pack (Suppress_Array);
706
707   --  To add a new check type to GNAT, the following steps are required:
708
709   --    1.  Add an entry to Snames spec for the new name
710   --    2.  Add an entry to the definition of Check_Id above (very important:
711   --        these definitions should be in the same order in Snames and here)
712   --    3.  Add a new function to Checks to handle the new check test
713   --    4.  Add a new Do_xxx_Check flag to Sinfo (if required)
714   --    5.  Add appropriate checks for the new test
715
716   --  The following provides precise details on the mode used to generate
717   --  code for intermediate operations in expressions for signed integer
718   --  arithmetic (and how to generate overflow checks if enabled). Note
719   --  that this only affects handling of intermediate results. The final
720   --  result must always fit within the target range, and if overflow
721   --  checking is enabled, the check on the final result is against this
722   --  target range.
723
724   type Overflow_Mode_Type is (
725      Not_Set,
726      --  Dummy value used during initialization process to show that the
727      --  corresponding value has not yet been initialized.
728
729      Strict,
730      --  Operations are done in the base type of the subexpression. If
731      --  overflow checks are enabled, then the check is against the range
732      --  of this base type.
733
734      Minimized,
735      --  Where appropriate, intermediate arithmetic operations are performed
736      --  with an extended range, using Long_Long_Integer if necessary. If
737      --  overflow checking is enabled, then the check is against the range
738      --  of Long_Long_Integer.
739
740      Eliminated);
741      --  In this mode arbitrary precision arithmetic is used as needed to
742      --  ensure that it is impossible for intermediate arithmetic to cause an
743      --  overflow. In this mode, intermediate expressions are not affected by
744      --  the overflow checking mode, since overflows are eliminated.
745
746   subtype Minimized_Or_Eliminated is
747     Overflow_Mode_Type range Minimized .. Eliminated;
748   --  Define subtype so that clients don't need to know ordering. Note that
749   --  Overflow_Mode_Type is not marked as an ordered enumeration type.
750
751   --  The following structure captures the state of check suppression or
752   --  activation at a particular point in the program execution.
753
754   type Suppress_Record is record
755      Suppress : Suppress_Array;
756      --  Indicates suppression status of each possible check
757
758      Overflow_Mode_General : Overflow_Mode_Type;
759      --  This field indicates the mode for handling code generation and
760      --  overflow checking (if enabled) for intermediate expression values.
761      --  This applies to general expressions outside assertions.
762
763      Overflow_Mode_Assertions : Overflow_Mode_Type;
764      --  This field indicates the mode for handling code generation and
765      --  overflow checking (if enabled) for intermediate expression values.
766      --  This applies to any expression occuring inside assertions.
767   end record;
768
769   -----------------------------------
770   -- Global Exception Declarations --
771   -----------------------------------
772
773   --  This section contains declarations of exceptions that are used
774   --  throughout the compiler or in other GNAT tools.
775
776   Unrecoverable_Error : exception;
777   --  This exception is raised to immediately terminate the compilation of the
778   --  current source program. Used in situations where things are bad enough
779   --  that it doesn't seem worth continuing (e.g. max errors reached, or a
780   --  required file is not found). Also raised when the compiler finds itself
781   --  in trouble after an error (see Comperr).
782
783   Terminate_Program : exception;
784   --  This exception is raised to immediately terminate the tool being
785   --  executed. Each tool where this exception may be raised must have a
786   --  single exception handler that contains only a null statement and that is
787   --  the last statement of the program. If needed, procedure Set_Exit_Status
788   --  is called with the appropriate exit status before raising
789   --  Terminate_Program.
790
791   ---------------------------------
792   -- Parameter Mechanism Control --
793   ---------------------------------
794
795   --  Function and parameter entities have a field that records the passing
796   --  mechanism. See specification of Sem_Mech for full details. The following
797   --  subtype is used to represent values of this type:
798
799   subtype Mechanism_Type is Int range -2 .. Int'Last;
800   --  Type used to represent a mechanism value. This is a subtype rather than
801   --  a type to avoid some annoying processing problems with certain routines
802   --  in Einfo (processing them to create the corresponding C). The values in
803   --  the range -2 .. 0 are used to represent mechanism types declared as
804   --  named constants in the spec of Sem_Mech. Positive values are used for
805   --  the case of a pragma C_Pass_By_Copy that sets a threshold value for the
806   --  mechanism to be used. For example if pragma C_Pass_By_Copy (32) is given
807   --  then Default_C_Record_Mechanism is set to 32, and the meaning is to use
808   --  By_Reference if the size is greater than 32, and By_Copy otherwise.
809
810   ------------------------------
811   -- Run-Time Exception Codes --
812   ------------------------------
813
814   --  When the code generator generates a run-time exception, it provides a
815   --  reason code which is one of the following. This reason code is used to
816   --  select the appropriate run-time routine to be called, determining both
817   --  the exception to be raised, and the message text to be added.
818
819   --  The prefix CE/PE/SE indicates the exception to be raised
820   --    CE = Constraint_Error
821   --    PE = Program_Error
822   --    SE = Storage_Error
823
824   --  The remaining part of the name indicates the message text to be added,
825   --  where all letters are lower case, and underscores are converted to
826   --  spaces (for example CE_Invalid_Data adds the text "invalid data").
827
828   --  To add a new code, you need to do the following:
829
830   --    1. Assign a new number to the reason. Do not renumber existing codes,
831   --       since this causes compatibility/bootstrap issues, so always add the
832   --       new code at the end of the list.
833
834   --    2. Update the contents of the array Kind
835
836   --    3. Modify the corresponding definitions in types.h, including the
837   --       definition of last_reason_code.
838
839   --    4. Add the name of the routines in exp_ch11.Get_RT_Exception_Name
840
841   --    5. Add a new routine in Ada.Exceptions with the appropriate call and
842   --       static string constant. Note that there is more than one version
843   --       of a-except.adb which must be modified.
844
845   --  Note on ordering of references. For the tables in Ada.Exceptions units,
846   --  usually the ordering does not matter, and we use the same ordering as
847   --  is used here.
848
849   type RT_Exception_Code is
850     (CE_Access_Check_Failed,            -- 00
851      CE_Access_Parameter_Is_Null,       -- 01
852      CE_Discriminant_Check_Failed,      -- 02
853      CE_Divide_By_Zero,                 -- 03
854      CE_Explicit_Raise,                 -- 04
855      CE_Index_Check_Failed,             -- 05
856      CE_Invalid_Data,                   -- 06
857      CE_Length_Check_Failed,            -- 07
858      CE_Null_Exception_Id,              -- 08
859      CE_Null_Not_Allowed,               -- 09
860
861      CE_Overflow_Check_Failed,          -- 10
862      CE_Partition_Check_Failed,         -- 11
863      CE_Range_Check_Failed,             -- 12
864      CE_Tag_Check_Failed,               -- 13
865      PE_Access_Before_Elaboration,      -- 14
866      PE_Accessibility_Check_Failed,     -- 15
867      PE_Address_Of_Intrinsic,           -- 16
868      PE_Aliased_Parameters,             -- 17
869      PE_All_Guards_Closed,              -- 18
870      PE_Bad_Predicated_Generic_Type,    -- 19
871
872      PE_Current_Task_In_Entry_Body,     -- 20
873      PE_Duplicated_Entry_Address,       -- 21
874      PE_Explicit_Raise,                 -- 22
875      PE_Finalize_Raised_Exception,      -- 23
876      PE_Implicit_Return,                -- 24
877      PE_Misaligned_Address_Value,       -- 25
878      PE_Missing_Return,                 -- 26
879      PE_Overlaid_Controlled_Object,     -- 27
880      PE_Potentially_Blocking_Operation, -- 28
881      PE_Stubbed_Subprogram_Called,      -- 29
882
883      PE_Unchecked_Union_Restriction,    -- 30
884      PE_Non_Transportable_Actual,       -- 31
885      SE_Empty_Storage_Pool,             -- 32
886      SE_Explicit_Raise,                 -- 33
887      SE_Infinite_Recursion,             -- 34
888      SE_Object_Too_Large,               -- 35
889      PE_Stream_Operation_Not_Allowed,   -- 36
890      PE_Build_In_Place_Mismatch);       -- 37
891
892   Last_Reason_Code : constant :=
893     RT_Exception_Code'Pos (RT_Exception_Code'Last);
894   --  Last reason code
895
896   type Reason_Kind is (CE_Reason, PE_Reason, SE_Reason);
897   --  Categorization of reason codes by exception raised
898
899   Rkind : constant array (RT_Exception_Code range <>) of Reason_Kind :=
900             (CE_Access_Check_Failed            => CE_Reason,
901              CE_Access_Parameter_Is_Null       => CE_Reason,
902              CE_Discriminant_Check_Failed      => CE_Reason,
903              CE_Divide_By_Zero                 => CE_Reason,
904              CE_Explicit_Raise                 => CE_Reason,
905              CE_Index_Check_Failed             => CE_Reason,
906              CE_Invalid_Data                   => CE_Reason,
907              CE_Length_Check_Failed            => CE_Reason,
908              CE_Null_Exception_Id              => CE_Reason,
909              CE_Null_Not_Allowed               => CE_Reason,
910              CE_Overflow_Check_Failed          => CE_Reason,
911              CE_Partition_Check_Failed         => CE_Reason,
912              CE_Range_Check_Failed             => CE_Reason,
913              CE_Tag_Check_Failed               => CE_Reason,
914
915              PE_Access_Before_Elaboration      => PE_Reason,
916              PE_Accessibility_Check_Failed     => PE_Reason,
917              PE_Address_Of_Intrinsic           => PE_Reason,
918              PE_Aliased_Parameters             => PE_Reason,
919              PE_All_Guards_Closed              => PE_Reason,
920              PE_Bad_Predicated_Generic_Type    => PE_Reason,
921              PE_Current_Task_In_Entry_Body     => PE_Reason,
922              PE_Duplicated_Entry_Address       => PE_Reason,
923              PE_Explicit_Raise                 => PE_Reason,
924              PE_Finalize_Raised_Exception      => PE_Reason,
925              PE_Implicit_Return                => PE_Reason,
926              PE_Misaligned_Address_Value       => PE_Reason,
927              PE_Missing_Return                 => PE_Reason,
928              PE_Overlaid_Controlled_Object     => PE_Reason,
929              PE_Potentially_Blocking_Operation => PE_Reason,
930              PE_Stubbed_Subprogram_Called      => PE_Reason,
931              PE_Unchecked_Union_Restriction    => PE_Reason,
932              PE_Non_Transportable_Actual       => PE_Reason,
933              PE_Stream_Operation_Not_Allowed   => PE_Reason,
934              PE_Build_In_Place_Mismatch        => PE_Reason,
935
936              SE_Empty_Storage_Pool             => SE_Reason,
937              SE_Explicit_Raise                 => SE_Reason,
938              SE_Infinite_Recursion             => SE_Reason,
939              SE_Object_Too_Large               => SE_Reason);
940
941end Types;
942