-- or when a write procedure is executed on a full stream
Partition_RPC_Receiver : RPC_Receiver;
- -- Cache the RPC_Recevier passed by Establish_RPC_Receiver
+ -- Cache the RPC_Receiver passed by Establish_RPC_Receiver
type Anonymous_Task_Node;
entry Wake_Up
(Request : Request_Id_Type;
Length : Ada.Streams.Stream_Element_Count);
- -- To wake up the calling stub when the environnement task has
+ -- To wake up the calling stub when the environment task has
-- received a reply for this request
end Dispatcher;
New_Result : aliased Params_Stream_Type (R_Length);
begin
-- Adjust the Result stream size right now to be able to load
- -- the stream in one receive call. Create a temporary resutl
+ -- the stream in one receive call. Create a temporary result
-- that will be substituted to Do_RPC one
Streams.Allocate (New_Result);
Request := Last_Request;
-- << TODO >>
- -- ??? Avaibility check
+ -- ??? Availability check
if Last_Request = Request_Id_Type'Last then
Last_Request := Request_Id_Type'First;
(Header'Access,
Streams.Get_Stream_Size (Result'Access));
- -- Get a protocol method to comunicate with the remote
+ -- Get a protocol method to communicate with the remote
-- partition and give the message size
D (D_Communication,
Garbage_Collector.Allocate (Anonymous);
-- We subtracted the size of the header from the size of the
- -- global message in order to provide immediatly Params size
+ -- global message in order to provide immediately Params size
Anonymous.Element.Start
(Message_Id,
+2008-03-24 Ralf Wildenhues <Ralf.Wildenhues@gmx.de>
+
+ * 9drpc.adb, a-caldel-vms.adb, a-caldel.adb,
+ a-calend-vms.adb, a-calend.adb, a-calend.ads,
+ a-calfor.adb, a-chahan.ads, a-chtgke.adb,
+ a-cihama.ads, a-ciorse.adb, a-clrefi.ads,
+ a-cohama.ads, a-comlin.ads, a-coorse.adb,
+ a-crbtgk.adb, a-direct.adb, a-except-2005.adb,
+ a-except-2005.ads, a-except.adb, a-except.ads,
+ a-exexda.adb, a-exexpr-gcc.adb, a-exexpr.adb,
+ a-exextr.adb, a-filico.ads, a-finali.ads,
+ a-intnam-aix.ads, a-intnam-solaris.ads, a-ngcefu.adb,
+ a-ngelfu.adb, a-numaux-darwin.adb, a-numeri.ads,
+ a-sequio.ads, a-strbou.ads, a-strfix.adb,
+ checks.adb, exp_ch3.adb, exp_ch4.adb,
+ exp_ch4.ads, exp_ch5.adb, exp_ch6.adb,
+ exp_ch6.ads, exp_ch7.adb, exp_ch7.ads,
+ exp_ch9.adb, exp_ch9.ads, exp_dbug.adb,
+ exp_dbug.ads, exp_disp.adb, exp_dist.adb,
+ exp_dist.ads, exp_fixd.adb, exp_fixd.ads: Fix comment typos.
+
2008-03-24 Robert Dewar <dewar@adacore.com>
* s-tpopsp-posix.adb, s-tpopsp-solaris.adb, s-tpopsp-posix-foreign.adb,
-- Set up the Timed_Delay soft link to the non tasking version if it has
-- not been already set.
-- If tasking is present, Timed_Delay has already set this soft link, or
- -- this will be overriden during the elaboration of
+ -- this will be overridden during the elaboration of
-- System.Tasking.Initialization
if TSL.Timed_Delay = null then
use System.Traces;
- -- Earlier, System.Time_Opeations was used to implement the following
+ -- Earlier, System.Time_Operations was used to implement the following
-- operations. The idea was to avoid sucking in the tasking packages. This
-- did not work. Logically, we can't have it both ways. There is no way to
-- implement time delays that will have correct task semantics without
-- not been already set.
-- If tasking is present, Timed_Delay has already set this soft link, or
- -- this will be overriden during the elaboration of
+ -- this will be overridden during the elaboration of
-- System.Tasking.Initialization
if SSL.Timed_Delay = null then
-- Because time is measured in different units and from different origins
-- on various targets, a system independent model is incorporated into
- -- Ada.Calendar. The idea behing the design is to encapsulate all target
+ -- Ada.Calendar. The idea behind the design is to encapsulate all target
-- dependent machinery in a single package, thus providing a uniform
-- interface to all existing and any potential children.
End_Date : Time;
Elapsed_Leaps : out Natural;
Next_Leap_Sec : out Time);
- -- Elapsed_Leaps is the sum of the leap seconds that have occured on or
+ -- Elapsed_Leaps is the sum of the leap seconds that have occurred on or
-- after Start_Date and before (strictly before) End_Date. Next_Leap_Sec
- -- represents the next leap second occurence on or after End_Date. If
+ -- represents the next leap second occurrence on or after End_Date. If
-- there are no leaps seconds after End_Date, End_Of_Time is returned.
-- End_Of_Time can be used as End_Date to count all the leap seconds that
- -- have occured on or after Start_Date.
+ -- have occurred on or after Start_Date.
--
-- Note: Any sub seconds of Start_Date and End_Date are discarded before
-- the calculations are done. For instance: if 113 seconds is a leap
Next_Leap_Sec := End_Of_Time;
- -- Make sure that the end date does not excede the upper bound
+ -- Make sure that the end date does not exceed the upper bound
-- of Ada time.
if End_Date > Ada_High then
end if;
-- Perform the calculations only if the start date is within the leap
- -- second occurences table.
+ -- second occurrences table.
if Start_T <= Leap_Second_Times (Leap_Seconds_Count) then
function Is_Leap (Year : Year_Number) return Boolean is
begin
- -- Leap centenial years
+ -- Leap centennial years
if Year mod 400 = 0 then
return True;
- -- Non-leap centenial years
+ -- Non-leap centennial years
elsif Year mod 100 = 0 then
return False;
End_Date : Time_Rep;
Elapsed_Leaps : out Natural;
Next_Leap : out Time_Rep);
- -- Elapsed_Leaps is the sum of the leap seconds that have occured on or
+ -- Elapsed_Leaps is the sum of the leap seconds that have occurred on or
-- after Start_Date and before (strictly before) End_Date. Next_Leap_Sec
- -- represents the next leap second occurence on or after End_Date. If
+ -- represents the next leap second occurrence on or after End_Date. If
-- there are no leaps seconds after End_Date, End_Of_Time is returned.
-- End_Of_Time can be used as End_Date to count all the leap seconds that
- -- have occured on or after Start_Date.
+ -- have occurred on or after Start_Date.
--
-- Note: Any sub seconds of Start_Date and End_Date are discarded before
-- the calculations are done. For instance: if 113 seconds is a leap
-- Lower and upper bound of Ada time. The zero (0) value of type Time is
-- positioned at year 2150. Note that the lower and upper bound account
- -- for the non-leap centenial years.
+ -- for the non-leap centennial years.
Ada_Low : constant Time_Rep := -(61 * 366 + 188 * 365) * Nanos_In_Day;
Ada_High : constant Time_Rep := (60 * 366 + 190 * 365) * Nanos_In_Day;
Next_Leap := End_Of_Time;
- -- Make sure that the end date does not excede the upper bound
+ -- Make sure that the end date does not exceed the upper bound
-- of Ada time.
if End_Date > Ada_High then
end if;
-- Perform the calculations only if the start date is within the leap
- -- second occurences table.
+ -- second occurrences table.
if Start_T <= Leap_Second_Times (Leap_Seconds_Count) then
function Is_Leap (Year : Year_Number) return Boolean is
begin
- -- Leap centenial years
+ -- Leap centennial years
if Year mod 400 = 0 then
return True;
- -- Non-leap centenial years
+ -- Non-leap centennial years
elsif Year mod 100 = 0 then
return False;
-- Difference processing. This operation should be able to calculate
-- the difference between opposite values which are close to the end
- -- and start of Ada time. To accomodate the large range, we convert
+ -- and start of Ada time. To accommodate the large range, we convert
-- to seconds. This action may potentially round the two values and
-- either add or drop a second. We compensate for this issue in the
-- previous step.
Res_N := Time_Rep (Date);
-- If the target supports leap seconds, remove any leap seconds
- -- elapsed upto the input date.
+ -- elapsed up to the input date.
if Leap_Support then
Cumulative_Leap_Seconds
(Start_Of_Time, Res_N, Elapsed_Leaps, Next_Leap_N);
- -- The input time value may fall on a leap second occurence
+ -- The input time value may fall on a leap second occurrence
if Res_N >= Next_Leap_N then
Elapsed_Leaps := Elapsed_Leaps + 1;
is
-- The following constants represent the number of nanoseconds
-- elapsed since the start of Ada time to and including the non
- -- leap centenial years.
+ -- leap centennial years.
Year_2101 : constant Time_Rep := Ada_Low +
Time_Rep (49 * 366 + 151 * 365) * Nanos_In_Day;
end;
end if;
- -- Step 3: Non-leap centenial year adjustment in local time zone
+ -- Step 3: Non-leap centennial year adjustment in local time zone
-- In order for all divisions to work properly and to avoid more
- -- complicated arithmetic, we add fake Febriary 29s to dates which
- -- occur after a non-leap centenial year.
+ -- complicated arithmetic, we add fake February 29s to dates which
+ -- occur after a non-leap centennial year.
if Date_N >= Year_2301 then
Date_N := Date_N + Time_Rep (3) * Nanos_In_Day;
Res_N := Ada_Low;
- -- Step 2: Year processing and centenial year adjustment. Determine
+ -- Step 2: Year processing and centennial year adjustment. Determine
-- the number of four year segments since the start of Ada time and
-- the input date.
Count := (Year - Year_Number'First) / 4;
Res_N := Res_N + Time_Rep (Count) * Secs_In_Four_Years * Nano;
- -- Note that non-leap centenial years are automatically considered
+ -- Note that non-leap centennial years are automatically considered
-- leap in the operation above. An adjustment of several days is
-- required to compensate for this.
Time_Rep (Leap_Seconds_Count) * Nano;
-- The following constants denote February 28 during non-leap
- -- centenial years, the units are nanoseconds.
+ -- centennial years, the units are nanoseconds.
T_2100_2_28 : constant Time_Rep := Ada_Low +
(Time_Rep (49 * 366 + 150 * 365 + 59) * Secs_In_Day +
begin
Date_N := Time_Rep (Date);
- -- Dates which are 56 years appart fall on the same day, day light
- -- saving and so on. Non-leap centenial years violate this rule by
+ -- Dates which are 56 years apart fall on the same day, day light
+ -- saving and so on. Non-leap centennial years violate this rule by
-- one day and as a consequence, special adjustment is needed.
if Date_N > T_2100_2_28 then
-- Time is represented as a signed 64 bit integer count of nanoseconds
-- since the start of Ada time (1901-01-01 00:00:00.0 UTC). Time values
- -- produced by Time_Of are internaly normalized to UTC regardless of their
+ -- produced by Time_Of are internally normalized to UTC regardless of their
-- local time zone. This representation ensures correct handling of leap
-- seconds as well as performing arithmetic. In Ada 95, Split and Time_Of
-- will treat a time value as being in the local time zone, in Ada 2005,
-- Due to Earth's slowdown, the astronomical time is not as precise as the
-- International Atomic Time. To compensate for this inaccuracy, a single
-- leap second is added after the last day of June or December. The count
- -- of seconds during those occurences becomes:
+ -- of seconds during those occurrences becomes:
-- ... 58, 59, leap second 60, 0, 1, 2 ...
-- aggregate generated by xleaps
-- The algorithms that build the actual leap second values and discover
- -- how many leap seconds have occured between two dates do not need any
+ -- how many leap seconds have occurred between two dates do not need any
-- modification.
------------------------------
- -- Non-leap centenial years --
+ -- Non-leap centennial years --
------------------------------
- -- Over the range of Ada time, centenial years 2100, 2200 and 2300 are
+ -- Over the range of Ada time, centennial years 2100, 2200 and 2300 are
-- non-leap. As a consequence, seven non-leap years occur over the period
- -- of year - 4 to year + 4. Internaly, routines Split and Time_Of add or
+ -- of year - 4 to year + 4. Internally, routines Split and Time_Of add or
-- subtract a "fake" February 29 to facilitate the arithmetic involved.
-- The underlying type of Time has been chosen to be a 64 bit signed
procedure Check_Char (S : String; C : Character; Index : Integer);
-- Subsidiary to the two versions of Value. Determine whether the
- -- input strint S has character C at position Index. Raise
+ -- input string S has character C at position Index. Raise
-- Constraint_Error if there is a mismatch.
procedure Check_Digit (S : String; Index : Integer);
-- Ada 2005 AI 395: these functions are moved to Ada.Characters.Conversions
-- and are considered obsolete in Ada.Characters.Handling. However we do
-- not complain about this obsolescence, since in practice it is necessary
- -- to use these routines when creating code that is intended ro run in
+ -- to use these routines when creating code that is intended to run in
-- either Ada 95 or Ada 2005 mode.
function Is_Character (Item : Wide_Character) return Boolean;
-- Ada 2005 AI 395: these functions are moved to Ada.Characters.Conversions
-- and are considered obsolete in Ada.Characters.Handling. However we do
-- not complain about this obsolescence, since in practice it is necessary
- -- to use these routines when creating code that is intended ro run in
+ -- to use these routines when creating code that is intended to run in
-- either Ada 95 or Ada 2005 mode.
function To_Character
end loop;
-- We have determined that Key is not already in the hash table, so
- -- the change is tenatively allowed. We now perform the standard
+ -- the change is tentatively allowed. We now perform the standard
-- checks to determine whether the hash table is locked (because you
-- cannot change an element while it's in use by Query_Element or
-- Update_Element), or if the container is busy (because moving a
procedure Reserve_Capacity (Container : in out Map; Capacity : Count_Type);
-- Adjusts the current capacity, by allocating a new buckets array. If the
-- requested capacity is less than the current capacity, then the capacity
- -- is contracted (to a value not less than the curent length). If the
+ -- is contracted (to a value not less than the current length). If the
-- requested capacity is greater than the current capacity, then the
-- capacity is expanded (to a value not less than what is requested). In
-- either case, the nodes are rehashed from the old buckets array onto the
procedure Delete (Container : in out Map; Key : Key_Type);
-- Searches for Key in the map (which involves calling both Hash and
-- Equivalent_Keys). If the search fails, then the operation raises
- -- Constraint_Eror. Otherwise it removes the node from the map and then
+ -- Constraint_Error. Otherwise it removes the node from the map and then
-- deallocates it. (This is the deletion analog of non-conditional
-- Insert. It is intended for use when you want to assert that the item is
-- already in the map.)
T : Tree_Type renames Container.Tree'Unrestricted_Access.all;
B : Natural renames T.Busy;
- -- Start of prccessing for Iterate
+ -- Start of processing for Iterate
begin
B := B + 1;
-- response file.
--
-- Each non empty line of the response file contains one or several
- -- arguments sparated by white space. Empty lines or lines containing only
+ -- arguments separated by white space. Empty lines or lines containing only
-- white space are ignored. Arguments containing white space or a double
-- quote ('"')must be quoted. A double quote inside a quote string is
-- indicated by two consecutive double quotes. Example: "-Idir with quote
procedure Reserve_Capacity (Container : in out Map; Capacity : Count_Type);
-- Adjusts the current capacity, by allocating a new buckets array. If the
-- requested capacity is less than the current capacity, then the capacity
- -- is contracted (to a value not less than the curent length). If the
+ -- is contracted (to a value not less than the current length). If the
-- requested capacity is greater than the current capacity, then the
-- capacity is expanded (to a value not less than what is requested). In
-- either case, the nodes are rehashed from the old buckets array onto the
procedure Delete (Container : in out Map; Key : Key_Type);
-- Searches for Key in the map (which involves calling both Hash and
-- Equivalent_Keys). If the search fails, then the operation raises
- -- Constraint_Eror. Otherwise it removes the node from the map and then
+ -- Constraint_Error. Otherwise it removes the node from the map and then
-- deallocates it. (This is the deletion analog of non-conditional
-- Insert. It is intended for use when you want to assert that the item is
-- already in the map.)
Failure : constant Exit_Status := 1;
-- The following locations support the operation of the package
- -- Ada.Command_Line.Remove, whih provides facilities for logically
+ -- Ada.Command_Line.Remove, which provides facilities for logically
-- removing arguments from the command line. If one of the remove
-- procedures is called in this unit, then Remove_Args/Remove_Count
-- are set to indicate which arguments are removed. If no such calls
------------------------------
-- These subprograms provide functional notation for access to fields
- -- of a node, and procedural notation for modifiying these fields.
+ -- of a node, and procedural notation for modifying these fields.
function Color (Node : Node_Access) return Color_Type;
pragma Inline (Color);
T : Tree_Type renames Container.Tree'Unrestricted_Access.all;
B : Natural renames T.Busy;
- -- Start of prccessing for Iterate
+ -- Start of processing for Iterate
begin
B := B + 1;
-- is not a search and the only comparisons that occur are with
-- the hint and its neighbor.
- -- If Position is null, this is intepreted to mean that Key is
+ -- If Position is null, this is interpreted to mean that Key is
-- large relative to the nodes in the tree. If the tree is empty,
-- or Key is greater than the last node in the tree, then we're
-- done; otherwise the hint was "wrong" and we must search.
-- equivalent node. That wouldn't break any container invariants,
-- but our rule above says that new nodes always get inserted
-- after equivalent nodes. So here we test whether Key is both
- -- less than the hint and and equal to or greater than the hint's
+ -- less than the hint and equal to or greater than the hint's
-- previous neighbor, and if so insert it before the hint.
if Is_Less_Key_Node (Key, Hint) then
raise Status_Error;
else
- -- Reset Entry_Fatched and return the entry
+ -- Reset Entry_Fetched and return the entry
Search.Value.Entry_Fetched := False;
Directory_Entry := Search.Value.Dir_Entry;
-- is deferred before the reraise operation.
-- Save_Occurrence variations: As the management of the private data
- -- attached to occurrences is delicate, wether or not pointers to such
+ -- attached to occurrences is delicate, whether or not pointers to such
-- data has to be copied in various situations is better made explicit.
-- The following procedures provide an internal interface to help making
-- this explicit.
procedure Raise_From_Controlled_Operation
(X : Ada.Exceptions.Exception_Occurrence);
pragma No_Return (Raise_From_Controlled_Operation);
- -- Raise Program_Error, proviving information about X (an exception
+ -- Raise Program_Error, providing information about X (an exception
-- raised during a controlled operation) in the exception message.
procedure Reraise_Occurrence_Always (X : Exception_Occurrence);
-- purposes (e.g. implementing watchpoints in software or in the debugger).
-- In the GNAT technology itself, this interface is used to implement
- -- immediate aynschronous transfer of control and immediate abort on
+ -- immediate asynchronous transfer of control and immediate abort on
-- targets which do not provide for one thread interrupting another.
-- Note: this used to be in a separate unit called System.Poll, but that
-- builds may be done with bootstrap compilers that cannot handle these
-- additions. The full version of Ada.Exceptions can be found in the files
-- a-except-2005.ads/adb, and is used for all other builds where full Ada
--- 2005 functionality is required. in particular, it is used for building
+-- 2005 functionality is required. In particular, it is used for building
-- run times on all targets.
pragma Warnings (Off);
-- is deferred before the reraise operation.
-- Save_Occurrence variations: As the management of the private data
- -- attached to occurrences is delicate, wether or not pointers to such
+ -- attached to occurrences is delicate, whether or not pointers to such
-- data has to be copied in various situations is better made explicit.
-- The following procedures provide an internal interface to help making
-- this explicit.
-- builds may be done with bootstrap compilers that cannot handle these
-- additions. The full version of Ada.Exceptions can be found in the files
-- a-except-2005.ads/adb, and is used for all other builds where full Ada
--- 2005 functionality is required. in particular, it is used for building
+-- 2005 functionality is required. In particular, it is used for building
-- run times on all targets.
pragma Polling (Off);
procedure Raise_From_Controlled_Operation
(X : Ada.Exceptions.Exception_Occurrence);
pragma No_Return (Raise_From_Controlled_Operation);
- -- Raise Program_Error, proviving information about X (an exception
+ -- Raise Program_Error, providing information about X (an exception
-- raised during a controlled operation) in the exception message.
procedure Reraise_Occurrence_Always (X : Exception_Occurrence);
-- purposes (e.g. implementing watchpoints in software or in the debugger).
-- In the GNAT technology itself, this interface is used to implement
- -- immediate aynschronous transfer of control and immediate abort on
+ -- immediate asynchronous transfer of control and immediate abort on
-- targets which do not provide for one thread interrupting another.
-- Note: this used to be in a separate unit called System.Poll, but that
function Basic_Exception_Traceback
(X : Exception_Occurrence) return String;
-- Returns an image of the complete call chain associated with an
- -- exception occurence in its most basic form, that is as a raw sequence
+ -- exception occurrence in its most basic form, that is as a raw sequence
-- of hexadecimal binary addresses.
function Tailored_Exception_Traceback
Ptr : in out Natural)
is
Name : String (1 .. Exception_Name_Length (X));
- -- Bufer in which to fetch the exception name, in order to check
+ -- Buffer in which to fetch the exception name, in order to check
-- whether this is an internal _ABORT_SIGNAL or a regular occurrence.
Name_Ptr : Natural := Name'First - 1;
-- These come from "C++ ABI for Itanium: Exception handling", which is
-- the reference for GCC. They are used only when we are relying on
- -- back-end tables for exception propagation, which in turn is currenly
+ -- back-end tables for exception propagation, which in turn is currently
-- only the case for Zero_Cost_Exceptions in GNAT5.
-- Return codes from the GCC runtime functions used to propagate
Id : Exception_Id;
-- GNAT Exception identifier. This is filled by Propagate_Exception
-- and then used by the personality routine to determine if the context
- -- it examines contains a handler for the exception beeing propagated.
+ -- it examines contains a handler for the exception being propagated.
N_Cleanups_To_Trigger : Integer;
-- Number of cleanup only frames encountered in SEARCH phase. This is
-- by the personality routine through the accessors declared below. Ada
-- specific fields are thus always accessed through consistent layout, and
-- we expect the actual alignment to always be large enough to avoid traps
- -- from the C accesses to the common header. Besides, accessors aleviate
- -- the need for a C struct whole conterpart, both painful and errorprone
+ -- from the C accesses to the common header. Besides, accessors alleviate
+ -- the need for a C struct whole counterpart, both painful and error-prone
-- to maintain anyway.
type GNAT_GCC_Exception_Access is access all GNAT_GCC_Exception;
-----------
-- The current model implemented for the stack of occurrences is a
- -- simplification of previous attempts, which all prooved to be flawed or
+ -- simplification of previous attempts, which all proved to be flawed or
-- would have needed significant additional circuitry to be made to work
-- correctly.
-- interface.
-- The basic point is that arranging for an occurrence to always appear at
- -- most once on the stack requires a way to determine if a given occurence
+ -- most once on the stack requires a way to determine if a given occurrence
-- is already there, which is not as easy as it might seem.
-- An attempt was made to use the Private_Data pointer for this purpose.
-- but making this to work while still avoiding memory leaks is far
-- from trivial.
- -- The current scheme has the advantage of beeing simple, and induces
+ -- The current scheme has the advantage of being simple, and induces
-- extra costs only in reraise cases which is acceptable.
end Exception_Propagation;
is
pragma Unreferenced (Excep, Current, Reraised);
begin
- -- In the GNAT-SJLJ case this "stack" only exists implicitely, by way of
+ -- In the GNAT-SJLJ case this "stack" only exists implicitly, by way of
-- local occurrence declarations together with save/restore operations
-- generated by the front-end, and this routine has nothing to do.
-- the termination routine. Avoiding the second output is possible but so
-- far has been considered undesirable. It would mean changing the order
-- of outputs between the two runs with or without exception traces, while
- -- it seems preferrable to only have additional outputs in the former
+ -- it seems preferable to only have additional outputs in the former
-- case.
end Exception_Traces;
-- List_Controller --
---------------------
- -- Management of a bidirectional linked heterogenous list of
+ -- Management of a bidirectional linked heterogeneous list of
-- dynamically Allocated objects. To simplify the management of the
-- linked list, the First and Last elements are statically part of the
-- original List controller:
type Controlled is abstract new SFR.Root_Controlled with null record;
function "=" (A, B : Controlled) return Boolean;
- -- Need to be defined explictly because we don't want to compare the
+ -- Need to be defined explicitly because we don't want to compare the
-- hidden pointers
type Limited_Controlled is
System.OS_Interface.SIGGRANT; -- monitor mode granted
SIGRETRACT : constant Interrupt_ID :=
- System.OS_Interface.SIGRETRACT; -- monitor mode should be relinguished
+ System.OS_Interface.SIGRETRACT; -- monitor mode should be relinquished
SIGSOUND : constant Interrupt_ID :=
System.OS_Interface.SIGSOUND; -- sound control has completed
-- The following signals are reserved by the run time (FSU threads):
-- SIGFPE, SIGILL, SIGSEGV, SIGBUS, SIGTRAP, SIGTERM, SIGABRT, SIGINT,
--- SIGLWP, SIGALRM, SIGVTALRM, SIGAITING, SIGSTOP, SIGKILL
+-- SIGLWP, SIGALRM, SIGVTALRM, SIGWAITING, SIGSTOP, SIGKILL
-- The pragma Unreserve_All_Interrupts affects the following signal(s):
end Arccot;
--------------
- -- Arctcoth --
+ -- Arccoth --
--------------
function Arccoth (X : Complex) return Complex is
(Y : Float_Type'Base;
X : Float_Type'Base := 1.0)
return Float_Type'Base;
- -- Common code for arc tangent after cyele reduction
+ -- Common code for arc tangent after cycle reduction
----------
-- "**" --
-- --
------------------------------------------------------------------------------
--- File a-numaux.adb <- a-numaux-d arwin.adb
+-- File a-numaux.adb <- a-numaux-darwin.adb
package body Ada.Numerics.Aux is
-- result in the range 0 .. 3. The absolute value of X is at most Pi/4.
-- The following three functions implement Chebishev approximations
- -- of the trigoniometric functions in their reduced domain.
+ -- of the trigonometric functions in their reduced domain.
-- These approximations have been computed using Maple.
function Sine_Approx (X : Double) return Double;
3.14159_26535_89793_23846_26433_83279_50288_41971_69399_37511;
["03C0"] : constant := Pi;
- -- This is the greek letter Pi (for Ada 2005 AI-388). Note that it is
+ -- This is the Greek letter Pi (for Ada 2005 AI-388). Note that it is
-- conforming to have this constant present even in Ada 95 mode, as there
-- is no way for a normal mode Ada 95 program to reference this identifier.
-- used in this package and System.File_IO.
for File_Mode use
- (In_File => 0, -- System.FIle_IO.File_Mode'Pos (In_File)
+ (In_File => 0, -- System.File_IO.File_Mode'Pos (In_File)
Out_File => 2, -- System.File_IO.File_Mode'Pos (Out_File)
Append_File => 3); -- System.File_IO.File_Mode'Pos (Append_File)
-- is at least one Bounded_String argument from which the maximum
-- length can be obtained. For all such routines, the implementation
-- in this private part is simply a renaming of the corresponding
- -- routine in the super bouded package.
+ -- routine in the superbounded package.
-- The five exceptions are the * and Replicate routines operating on
-- character values. For these cases, we have a routine in the body
-- of Is_In, so that we are not dependent on inlining. Note that the search
-- function implementations are to be found in the auxiliary package
-- Ada.Strings.Search. Also the Move procedure is directly incorporated (ADAR
--- used a subunit for this procedure). number of errors having to do with
+-- used a subunit for this procedure). The number of errors having to do with
-- bounds of function return results were also fixed, and use of & removed for
-- efficiency reasons.
-- Check that a null-excluding component, formal or object is not
-- being assigned a null value. Otherwise generate a warning message
- -- and replace Expression (N) by a N_Contraint_Error node.
+ -- and replace Expression (N) by a N_Constraint_Error node.
if K /= N_Function_Specification then
Expr := Expression (N);
or else Is_Tag (Defining_Identifier (First_Comp))
-- Ada 2005 (AI-251): The following condition covers secondary
- -- tags but also the adjacent component contanining the offset
+ -- tags but also the adjacent component containing the offset
-- to the base of the object (component generated if the parent
-- has discriminants --- see Add_Interface_Tag_Components).
-- This is required to avoid the addition of the controller
Warning_Needed := True;
else
- -- Verify that at least one component has an initializtion
+ -- Verify that at least one component has an initialization
-- expression. No need for a warning on a type if all its
-- components have no initialization.
-- Local recursive function used to expand equality for nested
-- composite types. Used by Expand_Record/Array_Equality, Bodies
-- is a list on which to attach bodies of local functions that are
- -- created in the process. This is the responsability of the caller
+ -- created in the process. This is the responsibility of the caller
-- to insert those bodies at the right place. Nod provides the Sloc
-- value for generated code. Lhs and Rhs are the left and right sides
-- for the comparison, and Typ is the type of the arrays to compare.
procedure Expand_Concatenate_String (Cnode : Node_Id; Opnds : List_Id);
-- Routine to expand concatenation of 2-5 operands (in the list Operands)
- -- and replace node Cnode with the result of the contatenation. If there
+ -- and replace node Cnode with the result of the concatenation. If there
-- are two operands, they can be string or character. If there are more
-- than two operands, then are always of type string (i.e. the caller has
-- already converted character operands to strings in this case).
-- implement the target interface. This case corresponds with the
-- following example:
- -- function Op (Obj : Iface_1'Class) return access Ifac_2e'Class is
+ -- function Op (Obj : Iface_1'Class) return access Iface_2'Class is
-- begin
-- return new Iface_2'Class'(Obj);
-- end Op;
-- call to a build-in-place function, then access to the allocated
-- object must be passed to the function. Currently we limit such
-- functions to those with constrained limited result subtypes,
- -- but eventually we plan to expand the allowed forms of funtions
+ -- but eventually we plan to expand the allowed forms of functions
-- that are treated as build-in-place.
if Ada_Version >= Ada_05
-- Generate an additional object containing the address of the
-- returned object. The type of this second object declaration
- -- is the correct type required for the common proceessing
+ -- is the correct type required for the common processing
-- that is still performed by this subprogram. The displacement
-- of this pointer to reference the component associated with
-- the interface type will be done at the end of the common
-- call to a build-in-place function, then access to the allocated
-- object must be passed to the function. Currently we limit such
-- functions to those with constrained limited result subtypes,
- -- but eventually we plan to expand the allowed forms of funtions
+ -- but eventually we plan to expand the allowed forms of functions
-- that are treated as build-in-place.
if Ada_Version >= Ada_05
-- Let n be the number of array operands to be concatenated, Base_Typ
-- their base type, Ind_Typ their index type, and Arr_Typ the original
- -- array type to which the concatenantion operator applies, then the
+ -- array type to which the concatenation operator applies, then the
-- following subprogram is constructed:
-- [function Cnn (S1 : Base_Typ; ...; Sn : Base_Typ) return Base_Typ is
-- Note that this does *not* fix the array concatenation bug when the
-- low bound is Integer'first sibce that bug comes from the pointer
- -- dereferencing an unconstrained array. An there we need a constraint
+ -- dereferencing an unconstrained array. And there we need a constraint
-- check to make sure the length of the concatenated array is ok. ???
Insert_Action (Cnode, Func_Body, Suppress => All_Checks);
procedure Rewrite_Coextension (N : Node_Id);
-- Static coextensions have the same lifetime as the entity they
- -- constrain. Such occurences can be rewritten as aliased objects
+ -- constrain. Such occurrences can be rewritten as aliased objects
-- and their unrestricted access used instead of the coextension.
---------------------------------------
Desig := Subtype_Mark (Expression (N));
-- If context is constrained, use constrained subtype directly,
- -- so that the constant is not labelled as having a nomimally
+ -- so that the constant is not labelled as having a nominally
-- unconstrained subtype.
if Entity (Desig) = Base_Type (Dtyp) then
-- If the allocator is for a type which requires initialization, and
-- there is no initial value (i.e. operand is a subtype indication
- -- rather than a qualifed expression), then we must generate a call
+ -- rather than a qualified expression), then we must generate a call
-- to the initialization routine. This is done using an expression
-- actions node:
end if;
-- For packed arrays that are not bit-packed (i.e. the case of an array
- -- with one or more index types with a non-coniguous enumeration type),
+ -- with one or more index types with a non-contiguous enumeration type),
-- we can always use the normal packed element get circuit.
if not Is_Bit_Packed_Array (Etype (Prefix (N))) then
Right_Opnd => Right_Opnd (N))));
-- We want this to appear as coming from source if original does (see
- -- tranformations in Expand_N_In).
+ -- transformations in Expand_N_In).
Set_Comes_From_Source (N, Cfs);
Set_Comes_From_Source (Right_Opnd (N), Cfs);
- -- Now analyze tranformed node
+ -- Now analyze transformed node
Analyze_And_Resolve (N, Typ);
end Expand_N_Not_In;
-- inherited.
function Has_Unconstrained_UU_Component (Typ : Node_Id) return Boolean;
- -- Determines whether a type has a subcompoment of an unconstrained
+ -- Determines whether a type has a subcomponent of an unconstrained
-- Unchecked_Union subtype. Typ is a record type.
-------------------------
begin
while Present (Comp) loop
- -- One component is sufficent
+ -- One component is sufficient
if Component_Is_Unconstrained_UU (Comp) then
return True;
begin
while Present (Variant) loop
- -- One component within a variant is sufficent
+ -- One component within a variant is sufficient
if Variant_Is_Unconstrained_UU (Variant) then
return True;
(TSS (Root_Type (Typl), TSS_Composite_Equality));
-- Otherwise expand the component by component equality. Note that
- -- we never use block-bit coparisons for records, because of the
+ -- we never use block-bit comparisons for records, because of the
-- problems with gaps. The backend will often be able to recombine
-- the separate comparisons that we generate here.
return;
end if;
- -- Arithemtic overflow checks for signed integer/fixed point types
+ -- Arithmetic overflow checks for signed integer/fixed point types
if Is_Signed_Integer_Type (Typ)
or else Is_Fixed_Point_Type (Typ)
if Do_Discriminant_Check (N) then
- -- Present the discrminant checking function to the backend,
+ -- Present the discriminant checking function to the backend,
-- so that it can inline the call to the function.
Add_Inlined_Body
-- call itself.
-- 5. Prefix of an address attribute (this is an error which
- -- is caught elsewhere, and the expansion would intefere
+ -- is caught elsewhere, and the expansion would interfere
-- with generating the error message).
if not Is_Packed (Typ) then
-- Do not do any expansion in the access type case if the
-- parent is a renaming, since this is an error situation
-- which will be caught by Sem_Ch8, and the expansion can
- -- intefere with this error check.
+ -- interfere with this error check.
if Is_Access_Type (Target_Type)
and then Is_Renamed_Object (N)
-- Start of processing for Has_Inferable_Discriminants
begin
- -- For identifiers and indexed components, it is sufficent to have a
+ -- For identifiers and indexed components, it is sufficient to have a
-- constrained Unchecked_Union nominal subtype.
if Nkind_In (N, N_Identifier, N_Indexed_Component) then
-- Lhs, Rhs are the record expressions to be compared, these
-- expressions need not to be analyzed but have to be side-effect free.
-- Bodies is a list on which to attach bodies of local functions that
- -- are created in the process. This is the responsability of the caller
- -- to insert those bodies at the right place. Nod provdies the Sloc
+ -- are created in the process. This is the responsibility of the caller
+ -- to insert those bodies at the right place. Nod provides the Sloc
-- value for generated code.
end Exp_Ch4;
function Make_Tag_Ctrl_Assignment (N : Node_Id) return List_Id;
-- Generate the necessary code for controlled and tagged assignment,
- -- that is to say, finalization of the target before, adjustement of
+ -- that is to say, finalization of the target before, adjustment of
-- the target after and save and restore of the tag and finalization
-- pointers which are not 'part of the value' and must not be changed
-- upon assignment. N is the original Assignment node.
Ensure_Defined (R_Type, N);
-- We normally compare addresses to find out which way round to
- -- do the loop, since this is realiable, and handles the cases of
+ -- do the loop, since this is reliable, and handles the cases of
-- parameters, conversions etc. But we can't do that in the bit
-- packed case or the VM case, because addresses don't work there.
and then not No_Ctrl_Actions (N)
then
- -- Call TSS procedure for array assignment, passing the the
+ -- Call TSS procedure for array assignment, passing the
-- explicit bounds of right and left hand sides.
declare
-- discriminant checks are locally suppressed (as in extension
-- aggregate expansions) because otherwise the discriminant
-- check will be performed within the _assign call. It is also
- -- suppressed for assignmments created by the expander that
+ -- suppressed for assignments created by the expander that
-- correspond to initializations, where we do want to copy the
- -- tag (No_Ctrl_Actions flag set True). by the expander and we
+ -- tag (No_Ctrl_Actions flag set True) by the expander and we
-- do not need to mess with tags ever (Expand_Ctrl_Actions flag
-- is set True in this case).
and then not Discriminant_Checks_Suppressed (Empty))
then
-- Fetch the primitive op _assign and proper type to call it.
- -- Because of possible conflits between private and full view
+ -- Because of possible conflicts between private and full view
-- the proper type is fetched directly from the operation
-- profile.
Handled_Statement_Sequence =>
Make_Handled_Sequence_Of_Statements (Loc, Statements => L)));
- -- If no restrictions on aborts, protect the whole assignement
+ -- If no restrictions on aborts, protect the whole assignment
-- for controlled objects as per 9.8(11).
if Controlled_Type (Typ)
-- An optimization. If there are only two alternatives, and only
-- a single choice, then rewrite the whole case statement as an
- -- if statement, since this can result in susbequent optimizations.
+ -- if statement, since this can result in subsequent optimizations.
-- This helps not only with case statements in the source of a
-- simple form, but also with generated code (discriminant check
-- functions in particular)
-- implicit access formal to the access object, to ensure
-- that the return object is initialized in that case.
-- In this situation, the target of the assignment must
- -- be rewritten to denote a derference of the access to
+ -- be rewritten to denote a dereference of the access to
-- the return object passed in by the caller.
if Present (Init_Assignment) then
return;
end if;
- -- Note: we do not have to worry about validity chekcing of the for loop
+ -- Note: we do not have to worry about validity checking of the for loop
-- range bounds here, since they were frozen with constant declarations
-- and it is during that process that the validity checking is done.
-- Similarly, expand calls to RCI subprograms on which pragma
-- All_Calls_Remote applies. The rewriting will be reanalyzed
-- later. Do this only when the call comes from source since we do
- -- not want such a rewritting to occur in expanded code.
+ -- not want such a rewriting to occur in expanded code.
elsif Is_All_Remote_Call (N) then
Expand_All_Calls_Remote_Subprogram_Call (N);
-- Because of the presence of private types, the views of the
-- expression and the context may be different, so place an
-- unchecked conversion to the context type to avoid spurious
- -- errors, eg. when the expression is a numeric literal and
+ -- errors, e.g. when the expression is a numeric literal and
-- the context is private. If the expression is an aggregate,
-- use a qualified expression, because an aggregate is not a
-- legal argument of a conversion.
Typ : constant Entity_Id := Scope (DTC_Entity (Subp));
begin
- -- Handle private overriden primitives
+ -- Handle private overridden primitives
if not Is_CPP_Class (Typ) then
Check_Overriding_Operation (Subp);
-- If the object entity has a class-wide Etype, then we need to change
-- it to the result subtype of the function call, because otherwise the
- -- object will be class-wide without an explicit intialization and won't
+ -- object will be class-wide without an explicit initialization and won't
-- be allocated properly by the back end. It seems unclean to make such
-- a revision to the type at this point, and we should try to improve
-- this treatment when build-in-place functions with class-wide results
procedure Freeze_Subprogram (N : Node_Id);
-- generate the appropriate expansions related to Subprogram freeze
- -- nodes (e. g. the filling of the corresponding Dispatch Table for
+ -- nodes (e.g. the filling of the corresponding Dispatch Table for
-- Primitive Operations)
-- The following type defines the various forms of allocation used for the
--------------------------------------------------
function Find_Node_To_Be_Wrapped (N : Node_Id) return Node_Id;
- -- N is a node wich may generate a transient scope. Loop over the
+ -- N is a node which may generate a transient scope. Loop over the
-- parent pointers of N until it find the appropriate node to
-- wrap. It it returns Empty, it means that no transient scope is
-- needed in this context.
Is_Protected_Subprogram : Boolean;
Is_Task_Allocation_Block : Boolean;
Is_Asynchronous_Call_Block : Boolean) return Node_Id;
- -- Expand a the clean-up procedure for controlled and/or transient
+ -- Expand the clean-up procedure for controlled and/or transient
-- block, and/or task master or task body, or blocks used to
-- implement task allocation or asynchronous entry calls, or
-- procedures used to implement protected procedures. Clean is the
-- Finalization Management --
-----------------------------
- -- This part describe how Initialization/Adjusment/Finalization procedures
+ -- This part describe how Initialization/Adjustment/Finalization procedures
-- are generated and called. Two cases must be considered, types that are
-- Controlled (Is_Controlled flag set) and composite types that contain
-- controlled components (Has_Controlled_Component flag set). In the first
-- controlled components changes during execution. This controller
-- component is itself controlled and is attached to the upper-level
-- finalization chain. Its adjust primitive is in charge of calling adjust
- -- on the components and adusting the finalization pointer to match their
+ -- on the components and adjusting the finalization pointer to match their
-- new location (see a-finali.adb).
-- It is not possible to use a similar technique for arrays that have
-------------------------------
-- This procedure is called each time a transient block has to be inserted
- -- that is to say for each call to a function with unconstrained ot tagged
+ -- that is to say for each call to a function with unconstrained or tagged
-- result. It creates a new scope on the stack scope in order to enclose
-- all transient variables generated
-- creating this final list if necessary.
function Has_New_Controlled_Component (E : Entity_Id) return Boolean;
- -- E is a type entity. Give the same resul as Has_Controlled_Component
+ -- E is a type entity. Give the same result as Has_Controlled_Component
-- except for tagged extensions where the result is True only if the
-- latest extension contains a controlled component.
With_Attach : Node_Id) return Node_Id;
-- Attach the referenced object to the referenced Final Chain 'Flist_Ref'
-- With_Attach is an expression of type Short_Short_Integer which can be
- -- either '0' to signify no attachment, '1' for attachement to a simply
- -- linked list or '2' for attachement to a doubly linked list.
+ -- either '0' to signify no attachment, '1' for attachment to a simply
+ -- linked list or '2' for attachment to a doubly linked list.
function Make_Init_Call
(Ref : Node_Id;
-- been previously analyzed) that references the object to be initialized.
-- Typ is the expected type of Ref, which is either a controlled type
-- (Is_Controlled) or a type with controlled components (Has_Controlled).
- -- With_Attach is an integer expression which is the attchment level,
+ -- With_Attach is an integer expression which is the attachment level,
-- see System.Finalization_Implementation.Attach_To_Final_List for the
-- documentation of Nb_Link.
--
procedure Wrap_Transient_Declaration (N : Node_Id);
-- N is an object declaration. Expand the finalization calls after the
- -- declaration and make the outer scope beeing the transient one.
+ -- declaration and make the outer scope being the transient one.
procedure Wrap_Transient_Expression (N : Node_Id);
-- N is a sub-expression. Expand a transient block around an expression
Formals : List_Id;
Decls : List_Id) return Entity_Id;
-- Generate an access type for each actual parameter in the list Actuals.
- -- Cleate an encapsulating record that contains all the actuals and return
+ -- Create an encapsulating record that contains all the actuals and return
-- its type. Generate:
-- type Ann1 is access all <actual1-type>
-- ...
Formals : out List_Id);
-- Given a dispatching call, extract the entity of the name of the call,
-- its object parameter, its actual parameters and the formal parameters
- -- of the overriden interface-level version.
+ -- of the overridden interface-level version.
procedure Extract_Entry
(N : Node_Id;
Pdef := Defining_Identifier (P);
-- The privals are declared before the current body is
- -- analyzed. for visibility reasons. Set their Sloc so
+ -- analyzed, for visibility reasons. Set their Sloc so
-- that it is consistent with their renaming declaration,
-- to prevent anomalies in gdb.
-- but it does have an activation chain on which to store the tasks
-- temporarily. On successful return, the tasks on this chain are
-- moved to the chain passed in by the caller. We do not build an
- -- Activatation_Chain_Entity for an N_Extended_Return_Statement,
+ -- Activation_Chain_Entity for an N_Extended_Return_Statement,
-- because we do not want to build a call to Activate_Tasks. Task
-- activation is the responsibility of the caller.
function Overriding_Possible
(Iface_Prim_Op : Entity_Id;
Proc_Nam : Entity_Id) return Boolean;
- -- Determine whether a primitive operation can be overriden by the
+ -- Determine whether a primitive operation can be overridden by the
-- wrapper. Iface_Prim_Op is the candidate primitive operation of an
-- abstract interface type, Proc_Nam is the generated entry wrapper.
Iface_Prim_Op := Alias (Iface_Prim_Op);
end loop;
- -- The current primitive operation can be overriden by the
+ -- The current primitive operation can be overridden by the
-- generated entry wrapper.
if Overriding_Possible (Iface_Prim_Op, Proc_Nam) then
Iface_Prim_Op := Alias (Iface_Prim_Op);
end loop;
- -- The current primitive operation can be overriden by
+ -- The current primitive operation can be overridden by
-- the generated entry wrapper.
if Overriding_Possible (Iface_Prim_Op, Proc_Nam) then
end loop Examine_Interfaces;
end if;
- -- Return if no interface primitive can be overriden
+ -- Return if no interface primitive can be overridden
return Empty;
-- The first three declarations were already inserted ahead of the accept
-- statement by the Expand_Accept_Declarations procedure, which was called
- -- directly from the semantics during analysis of the accept. statement,
+ -- directly from the semantics during analysis of the accept statement,
-- before analyzing its contained statements.
-- The declarations from the N_Accept_Statement, as noted in Sinfo, come
Current_Node := Sub;
-- Generate an overriding primitive operation specification for
- -- this subprogram if the protected type implements an inerface.
+ -- this subprogram if the protected type implements an interface.
if Ada_Version >= Ada_05
and then
Expression =>
D_Disc));
- -- Do the assignement at this stage only because the evaluation of the
+ -- Do the assignment at this stage only because the evaluation of the
-- expression must not occur before (see ACVC C97302A).
Append_To (Stmts,
Next (Stmt);
end loop;
- -- Do the assignement at this stage only because the evaluation
+ -- Do the assignment at this stage only because the evaluation
-- of the expression must not occur before (see ACVC C97302A).
Insert_Before (Stmt,
procedure Establish_Task_Master (N : Node_Id);
-- Given a subprogram body, or a block statement, or a task body, this
- -- proccedure makes the necessary transformations required of a task
+ -- procedure makes the necessary transformations required of a task
-- master (add Enter_Master call at start, and establish a cleanup
-- routine to make sure Complete_Master is called on exit).
-- Expand the entry barrier into a function. This is called directly
-- from Analyze_Entry_Body so that the discriminals and privals of the
-- barrier can be attached to the function declaration list, and a new
- -- set prepared for the entry body procedure, bedore the entry body
+ -- set prepared for the entry body procedure, before the entry body
-- statement sequence can be expanded. The resulting function is analyzed
-- now, within the context of the protected object, to resolve calls to
-- other protected functions.
procedure Set_Discriminals (Dec : Node_Id);
-- Replace discriminals in a protected type for use by the
-- next protected operation on the type. Each operation needs a
- -- new set of discirminals, since it needs a unique renaming of
+ -- new set of discriminals, since it needs a unique renaming of
-- the discriminant fields in the record used to implement the
-- protected type.
Add_Str_To_Name_Buffer ("__");
end if;
- -- Otherwise get name and note if it is a NPBE
+ -- Otherwise get name and note if it is a BNPE
Get_Name_String_And_Append (Chars (E));
-- For global entities, the encoded name includes all components of the
-- fully expanded name (but omitting Standard at the start). For example,
-- if a library level child package P.Q has an embedded package R, and
- -- there is an entity in this embdded package whose name is S, the encoded
+ -- there is an entity in this embedded package whose name is S, the encoded
-- name will include the components p.q.r.s.
-- For local entities, the encoded name only includes the components up to
-- The size of the objects typed as x should be obtained from the
-- structure of x (and x___XVE, if applicable) as for ordinary types
-- unless there is a variable named x___XVZ, which, if present, will
- -- hold the the size (in bits) of x.
+ -- hold the size (in bits) of x.
-- The type x will either be a subtype of y (see also Subtypes of
-- Variant Records, below) or will contain no fields at all. The layout,
-- Character types are enumeration types at least one of whose enumeration
-- literals is a character literal. Enumeration literals are usually simply
-- represented using their identifier names. If the enumeration literal is
- -- a character literal, the name aencoded as described in the following
+ -- a character literal, the name is encoded as described in the following
-- paragraph.
-- A name QUhh, where each 'h' is a lower-case hexadecimal digit, stands
-- Set Name_Buffer and Name_Len to the external name of one secondary
-- dispatch table of Typ. If the interface has been inherited from some
-- ancestor then Ancestor_Typ is such node (in this case the secondary DT
- -- is needed to handle overriden primitives); if there is no such ancestor
+ -- is needed to handle overridden primitives); if there is no such ancestor
-- then Ancestor_Typ is equal to Typ.
--
-- Internal rule followed for the generation of the external name:
function Is_Predefined_Dispatching_Alias (Prim : Entity_Id) return Boolean;
-- Returns true if Prim is not a predefined dispatching primitive but it is
- -- an alias of a predefined dispatching primitive (ie. through a renaming)
+ -- an alias of a predefined dispatching primitive (i.e. through a renaming)
function Original_View_In_Visible_Part (Typ : Entity_Id) return Boolean;
-- Check if the type has a private view or if the public view appears
Rewrite (Call_Node, New_Call);
-- Suppress all checks during the analysis of the expanded code
- -- to avoid the generation of spureous warnings under ZFP run-time.
+ -- to avoid the generation of spurious warnings under ZFP run-time.
Analyze_And_Resolve (Call_Node, Call_Typ, Suppress => All_Checks);
end Expand_Dispatching_Call;
-- If the type of the actual parameter comes from a limited
-- with-clause and the non-limited view is already available
- -- we replace the anonymous access type by a duplicate decla
+ -- we replace the anonymous access type by a duplicate decla-
-- ration whose designated type is the non-limited view
if Ekind (Actual_DDT) = E_Incomplete_Type
Result => Result);
Next_Elmt (AI_Tag_Elmt);
- -- Build the secondary table contaning pointers to primitives
+ -- Build the secondary table containing pointers to primitives
-- (used to give support to Generic Dispatching Constructors).
Make_Secondary_DT
Expression => New_Reference_To (Standard_True, Loc)));
-- In case of locally defined tagged type we declare the object
- -- contanining the dispatch table by means of a variable. Its
+ -- containing the dispatch table by means of a variable. Its
-- initialization is done later by means of an assignment. This is
-- required to generate its External_Tag.
procedure Set_All_DT_Position (Typ : Entity_Id) is
procedure Validate_Position (Prim : Entity_Id);
- -- Check that the position assignated to Prim is completely safe
+ -- Check that the position assigned to Prim is completely safe
-- (it has not been assigned to a previously defined primitive
-- operation of Typ)
begin
-- Set the DT_Position for each primitive operation. Perform some
- -- sanity checks to avoid to build completely inconsistant dispatch
+ -- sanity checks to avoid to build completely inconsistent dispatch
-- tables.
-- First stage: Set the DTC entity of all the primitive operations
-- Clear any previous value of the DT_Position attribute. In this
-- way we ensure that the final position of all the primitives is
- -- stablished by the following stages of this algorithm.
+ -- established by the following stages of this algorithm.
Set_DT_Position (Prim, No_Uint);
Set_Fixed_Prim (UI_To_Int (DT_Position (Prim)));
-- Overriding primitives must use the same entry as the
- -- overriden primitive.
+ -- overridden primitive.
elsif not Present (Abstract_Interface_Alias (Prim))
and then Present (Alias (Prim))
DT_Length := UI_To_Int (DT_Position (Prim));
end if;
- -- Ensure that the asignated position to non-predefined
+ -- Ensure that the assigned position to non-predefined
-- dispatching operations in the dispatch table is correct.
if not (Is_Predefined_Dispatching_Operation (Prim)
when others =>
Partition : Entity_Id;
- -- A variable containing the Partition_ID of the target parition
+ -- A variable containing the Partition_ID of the target partition
RPC_Receiver : Node_Id;
-- An expression whose value is the address of the target RPC
package Helpers is
- -- Routines to build distribtion helper subprograms for user-defined
+ -- Routines to build distribution helper subprograms for user-defined
-- types. For implementation of the Distributed systems annex (DSA)
-- over the PolyORB generic middleware components, it is necessary to
-- generate several supporting subprograms for each application data
-- We have an unconstrained Etyp: build the actual constrained
-- subtype for the value we just read from the stream.
- -- suubtype S is <actual subtype of Constant_Object>;
+ -- subtype S is <actual subtype of Constant_Object>;
Append_To (Decls,
Build_Actual_Subtype (Etyp,
Insertion_Node : Node_Id;
Body_Decls : List_Id);
-- Add primitive for the stub type, and the RPC receiver. The declarations
- -- are inserted after insertion_Node, while the bodies are appened at the
+ -- are inserted after insertion_Node, while the bodies are appended at the
-- end of Decls.
procedure Remote_Types_Tagged_Full_View_Encountered
-- happen?) and both were equal to the power of 2, then we would
-- be one bit off in this test, so for the left operand, we only
-- go up to the power of 2 - 1. This ensures that we do not get
- -- this anomolous case, and in practice the right operand is by
+ -- this anomalous case, and in practice the right operand is by
-- far the more likely one to be the constant.
Left_Size := UI_To_Int (RM_Size (Left_Type));
end if;
-- Now the result size must be at least twice the longer of
- -- the two sizes, to accomodate all possible results.
+ -- the two sizes, to accommodate all possible results.
Rsize := 2 * Int'Max (Left_Size, Right_Size);
-- General note on universal fixed. In the routines below, a fixed-point
-- type is always a specific fixed-point type or universal real, never
-- universal fixed. Universal fixed only appears as the result type of a
- -- division or multplication and in all such cases, the parent node, which
+ -- division or multiplication and in all such cases, the parent node, which
-- must be either a conversion node or a 'Round attribute reference node,
-- has the specific type information. In both cases, the parent node is
-- removed from the tree, and the appropriate routine in this package is