1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT RUN-TIME COMPONENTS                         --
4--                                                                          --
5--                       A D A . E X C E P T I O N S                        --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2015, Free Software Foundation, Inc.         --
10--                                                                          --
11-- This specification is derived from the Ada Reference Manual for use with --
12-- GNAT. The copyright notice above, and the license provisions that follow --
13-- apply solely to the  contents of the part following the private keyword. --
14--                                                                          --
15-- GNAT is free software;  you can  redistribute it  and/or modify it under --
16-- terms of the  GNU General Public License as published  by the Free Soft- --
17-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
18-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
19-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
20-- or FITNESS FOR A PARTICULAR PURPOSE.                                     --
21--                                                                          --
22-- As a special exception under Section 7 of GPL version 3, you are granted --
23-- additional permissions described in the GCC Runtime Library Exception,   --
24-- version 3.1, as published by the Free Software Foundation.               --
25--                                                                          --
26-- You should have received a copy of the GNU General Public License and    --
27-- a copy of the GCC Runtime Library Exception along with this program;     --
28-- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
29-- <http://www.gnu.org/licenses/>.                                          --
30--                                                                          --
31-- GNAT was originally developed  by the GNAT team at  New York University. --
32-- Extensive contributions were provided by Ada Core Technologies Inc.      --
33--                                                                          --
34------------------------------------------------------------------------------
35
36--  This version of Ada.Exceptions is used only for building the compiler
37--  and certain basic tools. The "real" version of Ada.Exceptions is in
38--  a-except-2005.ads/adb, and is used for all other builds where full Ada
39--  functionality is required. In particular, it is used for building run
40--  times on all targets.
41
42--  This version is limited to Ada 95 features. It omits Ada 2005 features
43--  such as the additional definitions of Exception_Name returning
44--  Wide_[Wide_]String. It differs from the version specified in the Ada 95 RM
45--  only in that it is declared Preelaborate (see declaration below for why
46--  this is done).
47
48--  The reason for this splitting off of a separate version is to support
49--  older bootstrap compilers that do not support Ada 2005 features, and
50--  Ada.Exceptions is part of the compiler sources.
51
52pragma Compiler_Unit_Warning;
53
54pragma Polling (Off);
55--  We must turn polling off for this unit, because otherwise we get
56--  elaboration circularities with ourself.
57
58with System;
59with System.Parameters;
60with System.Standard_Library;
61with System.Traceback_Entries;
62
63package Ada.Exceptions is
64   pragma Preelaborate;
65   --  We make this preelaborable. If we did not do this, then run time units
66   --  used by the compiler (e.g. s-soflin.ads) would run into trouble.
67   --  Conformance with Ada 95 is not an issue, since this version is used
68   --  only by the compiler.
69
70   type Exception_Id is private;
71
72   Null_Id : constant Exception_Id;
73
74   type Exception_Occurrence is limited private;
75
76   type Exception_Occurrence_Access is access all Exception_Occurrence;
77
78   Null_Occurrence : constant Exception_Occurrence;
79
80   function Exception_Name (X : Exception_Occurrence) return String;
81   --  Same as Exception_Name (Exception_Identity (X))
82
83   function Exception_Name (Id : Exception_Id) return String;
84
85   procedure Raise_Exception (E : Exception_Id; Message : String := "");
86   pragma No_Return (Raise_Exception);
87   --  Note: In accordance with AI-466, CE is raised if E = Null_Id
88
89   function Exception_Message (X : Exception_Occurrence) return String;
90
91   procedure Reraise_Occurrence (X : Exception_Occurrence);
92   --  Note: it would be really nice to give a pragma No_Return for this
93   --  procedure, but it would be wrong, since Reraise_Occurrence does return
94   --  if the argument is the null exception occurrence. See also procedure
95   --  Reraise_Occurrence_Always in the private part of this package.
96
97   function Exception_Identity (X : Exception_Occurrence) return Exception_Id;
98
99   function Exception_Information (X : Exception_Occurrence) return String;
100   --  The format of the exception information is as follows:
101   --
102   --    exception name (as in Exception_Name)
103   --    message (or a null line if no message)
104   --    PID=nnnn
105   --    0xyyyyyyyy 0xyyyyyyyy ...
106   --
107   --  The lines are separated by a ASCII.LF character
108   --  The nnnn is the partition Id given as decimal digits.
109   --  The 0x... line represents traceback program counter locations,
110   --  in order with the first one being the exception location.
111
112   --  Note on ordering: the compiler uses the Save_Occurrence procedure, but
113   --  not the function from Rtsfind, so it is important that the procedure
114   --  come first, since Rtsfind finds the first matching entity.
115
116   procedure Save_Occurrence
117     (Target : out Exception_Occurrence;
118      Source : Exception_Occurrence);
119
120   function Save_Occurrence
121     (Source : Exception_Occurrence)
122      return   Exception_Occurrence_Access;
123
124private
125   package SSL renames System.Standard_Library;
126   package SP renames System.Parameters;
127
128   subtype EOA is Exception_Occurrence_Access;
129
130   Exception_Msg_Max_Length : constant := SP.Default_Exception_Msg_Max_Length;
131
132   ------------------
133   -- Exception_Id --
134   ------------------
135
136   subtype Code_Loc is System.Address;
137   --  Code location used in building exception tables and for call addresses
138   --  when propagating an exception. Values of this type are created by using
139   --  Label'Address or extracted from machine states using Get_Code_Loc.
140
141   Null_Loc : constant Code_Loc := System.Null_Address;
142   --  Null code location, used to flag outer level frame
143
144   type Exception_Id is new SSL.Exception_Data_Ptr;
145
146   function EId_To_String (X : Exception_Id) return String;
147   function String_To_EId (S : String) return Exception_Id;
148   pragma Stream_Convert (Exception_Id, String_To_EId, EId_To_String);
149   --  Functions for implementing Exception_Id stream attributes
150
151   Null_Id : constant Exception_Id := null;
152
153   -------------------------
154   -- Private Subprograms --
155   -------------------------
156
157   function Exception_Name_Simple (X : Exception_Occurrence) return String;
158   --  Like Exception_Name, but returns the simple non-qualified name of the
159   --  exception. This is used to implement the Exception_Name function in
160   --  Current_Exceptions (the DEC compatible unit). It is called from the
161   --  compiler generated code (using Rtsfind, which does not respect the
162   --  private barrier, so we can place this function in the private part
163   --  where the compiler can find it, but the spec is unchanged.)
164
165   procedure Raise_Exception_Always (E : Exception_Id; Message : String := "");
166   pragma No_Return (Raise_Exception_Always);
167   pragma Export (Ada, Raise_Exception_Always, "__gnat_raise_exception");
168   --  This differs from Raise_Exception only in that the caller has determined
169   --  that for sure the parameter E is not null, and that therefore no check
170   --  for Null_Id is required. The expander converts Raise_Exception calls to
171   --  Raise_Exception_Always if it can determine this is the case. The Export
172   --  allows this routine to be accessed from Pure units.
173
174   procedure Raise_From_Signal_Handler
175     (E : Exception_Id;
176      M : System.Address);
177   pragma Export
178     (Ada, Raise_From_Signal_Handler,
179           "ada__exceptions__raise_from_signal_handler");
180   pragma No_Return (Raise_From_Signal_Handler);
181   --  This routine is used to raise an exception from a signal handler. The
182   --  signal handler has already stored the machine state (i.e. the state that
183   --  corresponds to the location at which the signal was raised). E is the
184   --  Exception_Id specifying what exception is being raised, and M is a
185   --  pointer to a null-terminated string which is the message to be raised.
186   --  Note that this routine never returns, so it is permissible to simply
187   --  jump to this routine, rather than call it. This may be appropriate for
188   --  systems where the right way to get out of signal handler is to alter the
189   --  PC value in the machine state or in some other way ask the operating
190   --  system to return here rather than to the original location.
191
192   procedure Raise_From_Controlled_Operation
193     (X : Ada.Exceptions.Exception_Occurrence);
194   pragma No_Return (Raise_From_Controlled_Operation);
195   pragma Export
196     (Ada, Raise_From_Controlled_Operation,
197           "__gnat_raise_from_controlled_operation");
198   --  Raise Program_Error, providing information about X (an exception raised
199   --  during a controlled operation) in the exception message.
200
201   procedure Reraise_Library_Exception_If_Any;
202   pragma Export
203     (Ada, Reraise_Library_Exception_If_Any,
204           "__gnat_reraise_library_exception_if_any");
205   --  If there was an exception raised during library-level finalization,
206   --  reraise the exception.
207
208   procedure Reraise_Occurrence_Always (X : Exception_Occurrence);
209   pragma No_Return (Reraise_Occurrence_Always);
210   --  This differs from Raise_Occurrence only in that the caller guarantees
211   --  that for sure the parameter X is not the null occurrence, and that
212   --  therefore this procedure cannot return. The expander uses this routine
213   --  in the translation of a raise statement with no parameter (reraise).
214
215   procedure Reraise_Occurrence_No_Defer (X : Exception_Occurrence);
216   pragma No_Return (Reraise_Occurrence_No_Defer);
217   --  Exactly like Reraise_Occurrence, except that abort is not deferred
218   --  before the call and the parameter X is known not to be the null
219   --  occurrence. This is used in generated code when it is known that
220   --  abort is already deferred.
221
222   function Triggered_By_Abort return Boolean;
223   --  Determine whether the current exception (if it exists) is an instance of
224   --  Standard'Abort_Signal.
225
226   -----------------------
227   -- Polling Interface --
228   -----------------------
229
230   --  The GNAT compiler has an option to generate polling calls to the Poll
231   --  routine in this package. Specifying the -gnatP option for a compilation
232   --  causes a call to Ada.Exceptions.Poll to be generated on every subprogram
233   --  entry and on every iteration of a loop, thus avoiding the possibility of
234   --  a case of unbounded time between calls.
235
236   --  This polling interface may be used for instrumentation or debugging
237   --  purposes (e.g. implementing watchpoints in software or in the debugger).
238
239   --  In the GNAT technology itself, this interface is used to implement
240   --  immediate asynchronous transfer of control and immediate abort on
241   --  targets which do not provide for one thread interrupting another.
242
243   --  Note: this used to be in a separate unit called System.Poll, but that
244   --  caused horrible circular elaboration problems between System.Poll and
245   --  Ada.Exceptions.
246
247   procedure Poll;
248   --  Check for asynchronous abort. Note that we do not inline the body.
249   --  This makes the interface more useful for debugging purposes.
250
251   --------------------------
252   -- Exception_Occurrence --
253   --------------------------
254
255   package TBE renames System.Traceback_Entries;
256
257   Max_Tracebacks : constant := 50;
258   --  Maximum number of trace backs stored in exception occurrence
259
260   subtype Tracebacks_Array is TBE.Tracebacks_Array (1 .. Max_Tracebacks);
261   --  Traceback array stored in exception occurrence
262
263   type Exception_Occurrence is record
264      Id : Exception_Id;
265      --  Exception_Identity for this exception occurrence
266
267      Msg_Length : Natural := 0;
268      --  Length of message (zero = no message)
269
270      Msg : String (1 .. Exception_Msg_Max_Length);
271      --  Characters of message
272
273      Exception_Raised : Boolean := False;
274      --  Set to true to indicate that this exception occurrence has actually
275      --  been raised. When an exception occurrence is first created, this is
276      --  set to False, then when it is processed by Raise_Current_Exception,
277      --  it is set to True. If Raise_Current_Exception is used to raise an
278      --  exception for which this flag is already True, then it knows that
279      --  it is dealing with the reraise case (which is useful to distinguish
280      --  for exception tracing purposes).
281
282      Pid : Natural := 0;
283      --  Partition_Id for partition raising exception
284
285      Num_Tracebacks : Natural range 0 .. Max_Tracebacks := 0;
286      --  Number of traceback entries stored
287
288      Tracebacks : Tracebacks_Array;
289      --  Stored tracebacks (in Tracebacks (1 .. Num_Tracebacks))
290   end record;
291
292   function "=" (Left, Right : Exception_Occurrence) return Boolean
293     is abstract;
294   --  Don't allow comparison on exception occurrences, we should not need
295   --  this, and it would not work right, because of the Msg and Tracebacks
296   --  fields which have unused entries not copied by Save_Occurrence.
297
298   function EO_To_String (X : Exception_Occurrence) return String;
299   function String_To_EO (S : String) return Exception_Occurrence;
300   pragma Stream_Convert (Exception_Occurrence, String_To_EO, EO_To_String);
301   --  Functions for implementing Exception_Occurrence stream attributes
302
303   Null_Occurrence : constant Exception_Occurrence := (
304     Id               => null,
305     Msg_Length       => 0,
306     Msg              => (others => ' '),
307     Exception_Raised => False,
308     Pid              => 0,
309     Num_Tracebacks   => 0,
310     Tracebacks       => (others => TBE.Null_TB_Entry));
311
312end Ada.Exceptions;
313