+2010-12-20 Ralf Wildenhues <Ralf.Wildenhues@gmx.de>
+
+ * projects.texi: Fix typos.
+ * gnat_rm.texi: Likewise.
+ * gnat_ugn.texi: Likewise.
+ * sem_util.adb: Fix typo in variable, typos in comments.
+ * a-btgbso.adb: Fix typos in comments.
+ * a-cbdlli.adb, a-cbhase.ads, a-cdlili.adb, a-cobove.adb,
+ a-coinve.adb, a-convec.adb, a-direct.ads, a-strunb-shared.adb,
+ a-strunb-shared.ads, a-stuten.ads, a-stwiun-shared.adb,
+ a-stwiun-shared.ads, a-stzunb-shared.adb, a-stzunb-shared.ads,
+ a-suenco.adb, a-suenst.adb, a-suewst.adb, a-suezst.adb, ali.ads,
+ aspects.ads, atree.ads, binde.adb, bindgen.adb, checks.adb,
+ checks.ads, einfo.ads, err_vars.ads, errout.adb, errout.ads,
+ exp_aggr.adb, exp_attr.adb, exp_cg.adb, exp_ch3.adb,
+ exp_ch4.adb, exp_ch5.adb, exp_ch6.adb, exp_ch7.adb,
+ exp_dbug.ads, exp_disp.adb, exp_fixd.ads, freeze.adb,
+ g-altive.ads, g-comlin.ads, g-excact.ads, g-mbdira.adb,
+ g-sechas.ads, g-sehash.ads, g-sha1.ads, g-sha224.ads,
+ g-sha256.ads, g-sha384.ads, g-sha512.ads, g-shsh32.ads,
+ g-shsh64.ads, g-socket.adb, g-socket.ads, g-sothco.ads,
+ gcc-interface/decl.c, gcc-interface/trans.c,
+ gcc-interface/utils2.c, gnat1drv.adb, init.c, inline.adb,
+ link.c, locales.c, make.adb, mingw32.h, namet.ads, osint.adb,
+ par-ch12.adb, par-ch13.adb, par-ch3.adb, par-ch4.adb,
+ par-prag.adb, par.adb, par_sco.adb, prepcomp.adb,
+ prj-conf.ads, prj-dect.adb, prj-env.adb, prj-env.ads,
+ prj-nmsc.adb, prj-tree.ads, prj-util.ads, prj.adb, prj.ads,
+ s-auxdec-vms-alpha.adb, s-auxdec-vms_64.ads, s-oscons-tmplt.c,
+ s-osinte-vxworks.ads, s-osprim-mingw.adb, s-regexp.adb,
+ s-stusta.adb, s-taprop-mingw.adb, s-taprop-solaris.adb,
+ scn.adb, scos.ads, sem.adb, sem_aggr.adb, sem_attr.adb,
+ sem_aux.adb, sem_aux.ads, sem_ch12.adb, sem_ch12.ads,
+ sem_ch13.adb, sem_ch13.ads, sem_ch3.adb, sem_ch4.adb,
+ sem_ch6.adb, sem_ch7.adb, sem_ch8.adb, sem_disp.adb,
+ sem_disp.ads, sem_eval.adb, sem_intr.adb, sem_prag.adb,
+ sem_res.adb, sem_scil.adb, sem_util.ads, sem_warn.adb,
+ sem_warn.ads, sinfo.ads, socket.c, styleg.adb, switch.ads,
+ sysdep.c, tb-alvxw.c, xoscons.adb: Likewise.
+
2010-12-13 Eric Botcazou <ebotcazou@adacore.com>
* gcc-interface/decl.c (gnat_to_gnu_entity) <E_General_Access_Type>:
"attempt to tamper with cursors (container is busy)";
end if;
- -- Note that there's no way to decide apriori whether the
+ -- Note that there's no way to decide a priori whether the
-- target has enough capacity for the union with source.
-- We cannot simply compare the sum of the existing lengths
-- to the capacity of the target, because equivalent items
-- logical end being manipulated). The only time we need to actually
-- initialize the nodes in the free store is if the node that becomes
-- inactive is not at the end of the list. The free store would then
- -- be discontigous and so its nodes would need to be linked in the
+ -- be discontiguous and so its nodes would need to be linked in the
-- traditional way.
--
-- ???
return False;
end if;
- if Position.Node = L.First then -- eliminates ealier disjunct
+ if Position.Node = L.First then -- eliminates earlier disjunct
return True;
end if;
procedure Symmetric_Difference (Target : in out Set; Source : Set);
-- The operation iterates over the Source set, searching for the element
-- in Target (calling Hash and Equivalent_Elements). If an equivalent
- -- elementis found, it is removed from Target; otherwise it is inserted
+ -- element is found, it is removed from Target; otherwise it is inserted
-- into Target.
function Symmetric_Difference (Left, Right : Set) return Set;
return False;
end if;
- if Position.Node = L.First then -- eliminates ealier disjunct
+ if Position.Node = L.First then -- eliminates earlier disjunct
return True;
end if;
-- There are two constraints we need to satisfy. The first constraint is
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the combined lengths. Note that we cannot
- -- simply add the lengths, because of the possibilty of overflow.
+ -- simply add the lengths, because of the possibility of overflow.
if LN > Count_Type'Last - RN then
raise Constraint_Error with "new length is out of range";
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the current length and the insertion
-- count. Note that we cannot simply add these values, because of the
- -- possibilty of overflow.
+ -- possibility of overflow.
if Old_Length > Count_Type'Last - Count then
raise Constraint_Error with "Count is out of range";
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the current length and the insertion
-- count. Note that we cannot simply add these values, because of the
- -- possibilty of overflow.
+ -- possibility of overflow.
if Old_Length > Count_Type'Last - Count then
raise Constraint_Error with "Count is out of range";
-- There are two constraints we need to satisfy. The first constraint is
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the combined lengths. Note that we cannot
- -- simply add the lengths, because of the possibilty of overflow.
+ -- simply add the lengths, because of the possibility of overflow.
if LN > Count_Type'Last - RN then
raise Constraint_Error with "new length is out of range";
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the current length and the insertion
-- count. Note that we cannot simply add these values, because of the
- -- possibilty of overflow.
+ -- possibility of overflow.
if Old_Length > Count_Type'Last - Count then
raise Constraint_Error with "Count is out of range";
Free (Src);
-- The new array has a range in the middle containing null access
- -- values. We now fill in that partion of the array with the new
+ -- values. We now fill in that partition of the array with the new
-- items.
for Idx in Before .. Index - 1 loop
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the current length and the insertion
-- count. Note that we cannot simply add these values, because of the
- -- possibilty of overflow.
+ -- possibility of overflow.
if Old_Length > Count_Type'Last - Count then
raise Constraint_Error with "Count is out of range";
Container.Elements := new Elements_Type'(Container.Last, Src);
- -- We have succesfully allocated a new internal array (with a
+ -- We have successfully allocated a new internal array (with a
-- smaller length than the old one, and containing a copy of
-- just the active elements in the container), so we can
-- deallocate the old array.
Container.Elements := new Elements_Type'(Container.Last, Src);
- -- We have succesfully allocated a new internal array (with a
+ -- We have successfully allocated a new internal array (with a
-- smaller length than the old one, and containing a copy of
-- just the active elements in the container), so it is now
-- safe to deallocate the old array.
Container.Elements.EA (Index_Subtype) := X.EA (Index_Subtype);
- -- We have moved the elements from the old interal array, so now we
+ -- We have moved the elements from the old internal array, so now we
-- can deallocate it.
Free (X);
-- There are two constraints we need to satisfy. The first constraint is
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the combined lengths. Note that we cannot
- -- simply add the lengths, because of the possibilty of overflow.
+ -- simply add the lengths, because of the possibility of overflow.
if LN > Count_Type'Last - RN then
raise Constraint_Error with "new length is out of range";
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the current length and the insertion
-- count. Note that we cannot simply add these values, because of the
- -- possibilty of overflow.
+ -- possibility of overflow.
if Old_Length > Count_Type'Last - Count then
raise Constraint_Error with "Count is out of range";
-- that a container cannot have more than Count_Type'Last elements, so
-- we must check the sum of the current length and the insertion
-- count. Note that we cannot simply add these values, because of the
- -- possibilty of overflow.
+ -- possibility of overflow.
if Old_Length > Count_Type'Last - Count then
raise Constraint_Error with "Count is out of range";
Container.Elements := new Elements_Type'(Container.Last, Src);
- -- We have succesfully allocated a new internal array (with a
+ -- We have successfully allocated a new internal array (with a
-- smaller length than the old one, and containing a copy of
-- just the active elements in the container), so it is now
-- safe to attempt to deallocate the old array. The old array
Container.Elements := new Elements_Type'(Container.Last, Src);
- -- We have succesfully allocated a new internal array (with a
+ -- We have successfully allocated a new internal array (with a
-- smaller length than the old one, and containing a copy of
-- just the active elements in the container), so it is now
-- safe to attempt to deallocate the old array. The old array
-- copy: Only copy if the destination file does not already
-- exist. If it already exists, Copy_File will fail.
--
- -- overwrite: Copy the file in all cases. Overwite an already
+ -- overwrite: Copy the file in all cases. Overwrite an already
-- existing destination file. This is the default if
-- no mode= is found in Form.
--
Reference (Empty_Shared_String'Access);
DR := Empty_Shared_String'Access;
- -- Left string is empty, return Rigth string
+ -- Left string is empty, return Right string
elsif LR.Last = 0 then
Reference (RR);
Reference (LR);
DR := LR;
- -- Overwise, allocate new shared string and fill data
+ -- Otherwise, allocate new shared string and fill data
else
DR := Allocate (LR.Last + RR.Last);
-- - Implicit sharing or copy-on-write. An Unbounded_String contains only
-- the reference to the data which is shared between several instances.
-- The shared data is reallocated only when its value is changed and
- -- the object mutation can't be used or it is unefficient to use it.
+ -- the object mutation can't be used or it is inefficient to use it.
-- - Object mutation. Shared data object can be reused without memory
-- reallocation when all of the following requirements are met:
-- Reference counting uses GCC builtin atomic operations, which allows to
-- safely share internal data between Ada tasks. Nevertheless, this doesn't
-- make objects of Unbounded_String thread-safe: each instance can't be
- -- accessed by several tasks simulatenously.
+ -- accessed by several tasks simultaneously.
with Ada.Strings.Maps;
private with Ada.Finalization;
function Allocate (Max_Length : Natural) return Shared_String_Access;
-- Allocates new Shared_String with at least specified maximum length.
- -- Actual maximum length of the allocated Shared_String can be sligtly
+ -- Actual maximum length of the allocated Shared_String can be slightly
-- greater. Returns reference to Empty_Shared_String when requested length
-- is zero.
-- values encoded in one of three ways (UTF-8, UTF-16BE, or UTF-16LE).
-- Typically used in connection with a Scheme parameter indicating which
-- of the encodings applies. This is not strictly a String value in the
- -- sense defined in the Ada RM, but in practice type String accomodates
+ -- sense defined in the Ada RM, but in practice type String accommodates
-- all possible 256 codes, and can be used to hold any sequence of 8-bit
-- codes. We use String directly rather than create a new type so that
-- all existing facilities for manipulating type String (e.g. the child
Reference (Empty_Shared_Wide_String'Access);
DR := Empty_Shared_Wide_String'Access;
- -- Left string is empty, return Rigth string.
+ -- Left string is empty, return Right string.
elsif LR.Last = 0 then
Reference (RR);
Reference (LR);
DR := LR;
- -- Overwise, allocate new shared string and fill data.
+ -- Otherwise, allocate new shared string and fill data.
else
DR := Allocate (LR.Last + RR.Last);
Last : Natural := 0;
Data : Wide_String (1 .. Max_Length);
-- Last is the index of last significant element of the Data. All
- -- elements with larger indecies are just an extra room.
+ -- elements with larger indices are just an extra room.
end record;
type Shared_Wide_String_Access is access all Shared_Wide_String;
function Allocate (Max_Length : Natural) return Shared_Wide_String_Access;
-- Allocates new Shared_Wide_String with at least specified maximum length.
- -- Actual maximum length of the allocated Shared_Wide_String can be sligtly
+ -- Actual maximum length of the allocated Shared_Wide_String can be slightly
-- greater. Returns reference to Empty_Shared_Wide_String when requested
-- length is zero.
Reference : Shared_Wide_String_Access := Empty_Shared_Wide_String'Access;
end record;
- -- The Unbounded_Wide_String uses several techniques to increasy speed of
+ -- The Unbounded_Wide_String uses several techniques to increase speed of
-- the application:
-- - implicit sharing or copy-on-write. Unbounded_Wide_String contains
-- only the reference to the data which is shared between several
-- instances. The shared data is reallocated only when its value is
- -- changed and the object mutation can't be used or it is unefficient to
+ -- changed and the object mutation can't be used or it is inefficient to
-- use it;
-- - object mutation. Shared data object can be reused without memory
-- reallocation when all of the following requirements are meat:
-- - shared data object don't used anywhere longer;
-- - its size is sufficient to store new value;
- -- - the gap after reuse is less then some threashold.
+ -- - the gap after reuse is less then some threshold.
-- - memory preallocation. Most of used memory allocation algorithms
- -- alligns allocated segment on the some boundary, thus some amount of
+ -- aligns allocated segment on the some boundary, thus some amount of
-- additional memory can be preallocated without any impact. Such
-- preallocated memory can used later by Append/Insert operations
-- without reallocation.
-- Reference counting uses GCC builtin atomic operations, which allows to
-- safely share internal data between Ada tasks. Nevertheless, this not
-- make objects of Unbounded_Wide_String thread-safe, so each instance
- -- can't be accessed by several tasks simulatenously.
+ -- can't be accessed by several tasks simultaneously.
pragma Stream_Convert (Unbounded_Wide_String, To_Unbounded, To_Wide_String);
-- Provide stream routines without dragging in Ada.Streams
Reference (Empty_Shared_Wide_Wide_String'Access);
DR := Empty_Shared_Wide_Wide_String'Access;
- -- Left string is empty, return Rigth string.
+ -- Left string is empty, return Right string.
elsif LR.Last = 0 then
Reference (RR);
Reference (LR);
DR := LR;
- -- Overwise, allocate new shared string and fill data.
+ -- Otherwise, allocate new shared string and fill data.
else
DR := Allocate (LR.Last + RR.Last);
Last : Natural := 0;
Data : Wide_Wide_String (1 .. Max_Length);
-- Last is the index of last significant element of the Data. All
- -- elements with larger indecies are just an extra room.
+ -- elements with larger indices are just an extra room.
end record;
type Shared_Wide_Wide_String_Access is access all Shared_Wide_Wide_String;
(Max_Length : Natural) return Shared_Wide_Wide_String_Access;
-- Allocates new Shared_Wide_Wide_String with at least specified maximum
-- length. Actual maximum length of the allocated Shared_Wide_Wide_String
- -- can be sligtly greater. Returns reference to
+ -- can be slightly greater. Returns reference to
-- Empty_Shared_Wide_Wide_String when requested length is zero.
Empty_Shared_Wide_Wide_String : aliased Shared_Wide_Wide_String (0);
Empty_Shared_Wide_Wide_String'Access;
end record;
- -- The Unbounded_Wide_Wide_String uses several techniques to increasy speed
+ -- The Unbounded_Wide_Wide_String uses several techniques to increase speed
-- of the application:
-- - implicit sharing or copy-on-write. Unbounded_Wide_Wide_String
-- contains only the reference to the data which is shared between
-- several instances. The shared data is reallocated only when its value
- -- is changed and the object mutation can't be used or it is unefficient
+ -- is changed and the object mutation can't be used or it is inefficient
-- to use it;
-- - object mutation. Shared data object can be reused without memory
-- reallocation when all of the following requirements are meat:
-- - shared data object don't used anywhere longer;
-- - its size is sufficient to store new value;
- -- - the gap after reuse is less then some threashold.
+ -- - the gap after reuse is less then some threshold.
-- - memory preallocation. Most of used memory allocation algorithms
- -- alligns allocated segment on the some boundary, thus some amount of
+ -- aligns allocated segment on the some boundary, thus some amount of
-- additional memory can be preallocated without any impact. Such
-- preallocated memory can used later by Append/Insert operations
-- without reallocation.
-- Reference counting uses GCC builtin atomic operations, which allows to
-- safely share internal data between Ada tasks. Nevertheless, this not
-- make objects of Unbounded_Wide_Wide_String thread-safe, so each instance
- -- can't be accessed by several tasks simulatenously.
+ -- can't be accessed by several tasks simultaneously.
pragma Stream_Convert
(Unbounded_Wide_Wide_String, To_Unbounded, To_Wide_Wide_String);
procedure Get_Continuation;
-- Reads a continuation byte of the form 10xxxxxx, shifts R left
-- by 6 bits, and or's in the xxxxxx to the low order 6 bits. On
- -- return Ptr is incremented. Raises exceptioon if continuation
+ -- return Ptr is incremented. Raises exception if continuation
-- byte does not exist or is invalid.
----------------------
procedure Get_Continuation;
-- Reads a continuation byte of the form 10xxxxxx, shifts R left
-- by 6 bits, and or's in the xxxxxx to the low order 6 bits. On
- -- return Ptr is incremented. Raises exceptioon if continuation
+ -- return Ptr is incremented. Raises exception if continuation
-- byte does not exist or is invalid.
----------------------
procedure Get_Continuation;
-- Reads a continuation byte of the form 10xxxxxx, shifts R left
-- by 6 bits, and or's in the xxxxxx to the low order 6 bits. On
- -- return Ptr is incremented. Raises exceptioon if continuation
+ -- return Ptr is incremented. Raises exception if continuation
-- byte does not exist or is invalid.
----------------------
Len := Len + 1;
Result (Len) := Wide_Character'Val (C);
- -- Codes in tne range 16#D800#..16#DFFF# should never appear in the
+ -- Codes in the range 16#D800#..16#DFFF# should never appear in the
-- input, since no valid Unicode characters are in this range (which
-- would conflict with the UTF-16 surrogate encodings). Similarly
-- codes in the range 16#FFFE#..16#FFFF conflict with BOM codes.
procedure Get_Continuation;
-- Reads a continuation byte of the form 10xxxxxx, shifts R left
-- by 6 bits, and or's in the xxxxxx to the low order 6 bits. On
- -- return Ptr is incremented. Raises exceptioon if continuation
+ -- return Ptr is incremented. Raises exception if continuation
-- byte does not exist or is invalid.
----------------------
-- Column number of definition
Visibility : Visibility_Kind;
- -- Visiblity of entity
+ -- Visibility of entity
Entity : Name_Id;
-- Name of entity
-- This package defines the aspects that are recognized by GNAT in aspect
-- specifications. It also contains the subprograms for storing/retrieving
--- aspect speciciations from the tree. The semantic processing for aspect
+-- aspect specifications from the tree. The semantic processing for aspect
-- specifications is found in Sem_Ch13.Analyze_Aspect_Specifications.
with Namet; use Namet;
-- True (i.e. the declaration nodes defined in the RM as permitting the
-- presence of Aspect_Specifications). However, it is possible for the
-- flag Has_Aspects to be set on other nodes as a result of Rewrite and
- -- Replace calls, and this function may be used to retrive the aspect
+ -- Replace calls, and this function may be used to retrieve the aspect
-- specifications for the original rewritten node in such cases.
procedure Set_Aspect_Specifications (N : Node_Id; L : List_Id);
-- Writes contents of Aspect_Specifications hash table to the tree file
procedure Tree_Read;
- -- Reads contents of Aspect_Specificatins hash table from the tree file
+ -- Reads contents of Aspect_Specifications hash table from the tree file
end Aspects;
-- This is similar to Rewrite, except that the old value of Old_Node is
-- not saved, and the New_Node is deleted after the replace, since it
-- is assumed that it can no longer be legitimately needed. The flag
- -- Is_Rewrite_Susbtitute will be False for the resulting node, unless
+ -- Is_Rewrite_Substitution will be False for the resulting node, unless
-- it was already true on entry, and Original_Node will not return the
-- original contents of the Old_Node, but rather the New_Node value (unless
-- Old_Node had already been rewritten using Rewrite). Replace also
-- A before the spec of B if it could. Since it could not, there it
-- must be the case that A depends on B. It is therefore a good idea
-- to put the body of B last so that if there is an elaboration order
- -- problem, we will find it (that's what pssimistic order is about)
+ -- problem, we will find it (that's what pessimistic order is about)
elsif Is_Waiting_Body (U1) and then Is_Waiting_Body (U2) then
declare
-- Write user linker options, i.e. the set of linker options that come
-- from all files other than GNAT internal files, Lgnat is left set to
-- point to the first entry from a GNAT internal file, or past the end
- -- of the entriers if there are no internal files.
+ -- of the entries if there are no internal files.
Lgnat := Linker_Options.Last + 1;
-- how we ensure that this condition is met.
-- First, we need to know for certain that the previous expression has
- -- been executed. This is done principly by the mechanism of calling
+ -- been executed. This is done principally by the mechanism of calling
-- Conditional_Statements_Begin at the start of any statement sequence
-- and Conditional_Statements_End at the end. The End call causes all
-- checks remembered since the Begin call to be discarded. This does
Target_Type : Entity_Id;
-- Used only if Do_Range_Check is set. Records the target type for
-- the check. We need this, because a check is a duplicate only if
- -- it has a the same target type (or more accurately one with a
+ -- it has the same target type (or more accurately one with a
-- range that is smaller or equal to the stored target type of a
-- saved check).
end record;
return;
end if;
- -- Here we do not know if the value is acceptable. Stricly we don't have
- -- to do anything, since if the alignment is bad, we have an erroneous
- -- program. However we are allowed to check for erroneous conditions and
- -- we decide to do this by default if the check is not suppressed.
+ -- Here we do not know if the value is acceptable. Strictly we don't
+ -- have to do anything, since if the alignment is bad, we have an
+ -- erroneous program. However we are allowed to check for erroneous
+ -- conditions and we decide to do this by default if the check is not
+ -- suppressed.
-- However, don't do the check if elaboration code is unwanted
return;
end if;
- -- Apply required constaint checks
+ -- Apply required constraint checks
if Is_Scalar_Type (Typ) then
Apply_Scalar_Range_Check (N, Typ);
-- If checks are off, then analyze the length check after
-- temporarily attaching it to the tree in case the relevant
- -- condition can be evaluted at compile time. We still want a
+ -- condition can be evaluated at compile time. We still want a
-- compile time warning in this case.
else
("use `OR ELSE` instead of OR?", P);
end if;
- -- If not short-circuited, we need the ckeck
+ -- If not short-circuited, we need the check
return True;
then
return;
- -- No check on a univeral real constant. The context will eventually
+ -- No check on a universal real constant. The context will eventually
-- convert it to a machine number for some target type, or report an
-- illegality.
then
return;
- -- If the expression denotes a component of a packed boolean arrray,
+ -- If the expression denotes a component of a packed boolean array,
-- no possible check applies. We ignore the old ACATS chestnuts that
-- involve Boolean range True..True.
Reason => CE_Invalid_Data),
Suppress => Validity_Check);
- -- If the expression is a a reference to an element of a bit-packed
+ -- If the expression is a reference to an element of a bit-packed
-- array, then it is rewritten as a renaming declaration. If the
-- expression is an actual in a call, it has not been expanded,
-- waiting for the proper point at which to do it. The same happens
return False;
end if;
- -- If we are in a case eexpression, and not part of the
+ -- If we are in a case expression, and not part of the
-- expression, then we return False, since a particular
-- branch may not always be elaborated
-- The checking code to be generated will freeze the
-- corresponding array type. However, we must freeze the
-- type now, so that the freeze node does not appear within
- -- the generated condional expression, but ahead of it.
+ -- the generated conditional expression, but ahead of it.
Freeze_Before (Ck_Node, T_Typ);
-- where the target object may be needed to determine the subtype to
-- check against (such as the cases of unconstrained formal parameters
-- and unconstrained aliased objects). For the case of unconstrained
- -- formals, the check is peformed only if the corresponding actual is
+ -- formals, the check is performed only if the corresponding actual is
-- constrained, i.e., whether Lhs'Constrained is True.
procedure Apply_Predicate_Check (N : Node_Id; Typ : Entity_Id);
-- which can never have a null value. This is set True for constant
-- access values initialized to a non-null value. This is also True for
-- all access parameters in Ada 83 and Ada 95 modes, and for access
--- parameters that explicily exclude null in Ada 2005.
+-- parameters that explicitly exclude null in Ada 2005.
--
-- This is used to avoid unnecessary resetting of the Is_Known_Non_Null
-- flag for such entities. In Ada 2005 mode, this is also used when
-- where Comes_From_Source is always False.
-- Corresponding_Protected_Entry (Node18)
--- Present in subrogram bodies. Set for subprogram bodies that implement
+-- Present in subprogram bodies. Set for subprogram bodies that implement
-- a protected type entry to point to the entity for the entry.
-- Corresponding_Record_Type (Node18)
-- Corresponding_Remote_Type (Node22)
-- Present in record types that describe the fat pointer structure for
--- Remote_Access_To_Subrogram types. References the original access type.
+-- Remote_Access_To_Subprogram types. References the original access
+-- type.
-- CR_Discriminant (Node23)
-- Present in discriminants of concurrent types. Denotes the homologous
-- Etype of the N_Null node is Empty.
-- Exception_Code (Uint22)
--- Present in exception entitites. Set to zero unless either an
+-- Present in exception entities. Set to zero unless either an
-- Import_Exception or Export_Exception pragma applies to the
-- pragma and specifies a Code value. See description of these
-- pragmas for details. Note that this field is relevant only if
-- First_Exit_Statement (Node8)
-- Present in E_Loop entity. The exit statements for a loop are chained
--- (in reverse order of appearence) using this field to point to the
+-- (in reverse order of appearance) using this field to point to the
-- first entry in the chain (last exit statement in the loop). The
-- entries are chained through the Next_Exit_Statement field of the
-- N_Exit_Statement node with Empty marking the end of the list.
-- Has_Anon_Block_Suffix (Flag201)
-- Present in all entities. Set if the entity is nested within one or
-- more anonymous blocks and the Chars field contains a name with an
--- anonymous block suffix (see Exp_Dbug for furthert details).
+-- anonymous block suffix (see Exp_Dbug for further details).
-- Has_Atomic_Components (Flag86) [implementation base type only]
-- Present in all types and objects. Set only for an array type or
-- Present in functions and generic functions. Set if there is one or
-- more missing return statements in the function. This is used to
-- control wrapping of the body in Exp_Ch6 to ensure that the program
--- error exeption is correctly raised in this case at runtime.
+-- error exception is correctly raised in this case at runtime.
-- Has_Up_Level_Access (Flag215)
-- Present in E_Variable and E_Constant entities. Set if the entity
-- Subprograms_For_Type (Node29)
-- Present in all type entities, and in subprogram entities. This is used
-- to hold a list of subprogram entities for subprograms associated with
--- the type, linked through the Suprogram_List field of the subprogram
+-- the type, linked through the Subprogram_List field of the subprogram
-- entity. Basically this is a way of multiplexing the single field to
-- hold more than one entity (since we ran out of space in some type
-- entities). This is currently used for Invariant_Procedure and also
Calign_Component_Size_4, -- natural for size <= 4, 4 for size >= 4
Calign_Storage_Unit); -- all components byte aligned
- ----------------------------------
- -- Floating Point Repesentation --
- ----------------------------------
+ -----------------------------------
+ -- Floating Point Representation --
+ -----------------------------------
type Float_Rep_Kind is (
IEEE_Binary, -- IEEE 754p conform binary format
(E : Entity_Id;
Nam : Name_Id) return Node_Id;
-- Searches the Rep_Item chain for a given entity E, for an instance of a
- -- rep item (pragma, attribute definition clause, or aspect specitication)
+ -- rep item (pragma, attribute definition clause, or aspect specification)
-- whose name matches the given name. If one is found, it is returned,
-- otherwise Empty is returned. Unlike the other Get routines for the
-- Rep_Item chain, this only returns items whose entity matches E (it
-- All of these variables are set when needed, so they do not need to be
-- initialized. However, there is code that saves and restores existing
-- values, which may malfunction in -gnatVa mode if the variable has never
- -- been iniitalized, so we initialize some variables to avoid exceptions
+ -- been initialized, so we initialize some variables to avoid exceptions
-- from invalid values in such cases.
------------------
-- if the loop does not exit, then the desired case will be left set to
-- Mixed_Case, this can happen if the name was not in canonical form,
-- and gets canonicalized on VMS. Possibly we could fix this by
- -- unconditinally canonicalizing these names ???
+ -- unconditionally canonicalizing these names ???
for J in 1 .. Last_Source_File loop
Get_Name_String (Full_Debug_Name (J));
-- are that an RM reference may follow in the form (RM .....) and a
-- right parenthesis may immediately follow the #. In the case of
-- continued messages, # can only appear at the end of a group of
- -- continuation messsages, except that \\ messages which always start
+ -- continuation messages, except that \\ messages which always start
-- a new line end the sequence from the point of view of this rule.
-- The idea is that for any use of -gnatj, it will still be the case
-- that a location reference appears only at the end of a line.
if Is_Delayed_Aggregate (Expr_Q) then
- -- This is either a subaggregate of a multidimentional array,
+ -- This is either a subaggregate of a multidimensional array,
-- or a component of an array type whose component type is
-- also an array. In the latter case, the expression may have
-- component associations that provide different bounds from
function Is_Flat (N : Node_Id; Dims : Int) return Boolean;
-- Return True iff the array N is flat (which is not trivial in the case
- -- of multidimensionsl aggregates).
+ -- of multidimensional aggregates).
-----------------------------
-- Check_Static_Components --
-- and T is B for the cases of Body_Version, or Version applied to a
-- subprogram acting as its own spec, and S for Version applied to a
-- subprogram spec or package. This sequence of code references the
- -- the unsigned constant created in the main program by the binder.
+ -- unsigned constant created in the main program by the binder.
-- A special exception occurs for Standard, where the string returned
-- is a copy of the library string in gnatvsn.ads.
or else Entity_Is_In_Main_Unit (Current_Scope)
then
-- Register a copy of the dispatching call node. Needed since the
- -- node containing a dispatching call is rewriten by the expander.
+ -- node containing a dispatching call is rewritten by the
+ -- expander.
declare
Copy : constant Node_Id := New_Copy (N);
Analyze (N, Suppress => All_Checks);
- -- Replace internal identifier of rewriten node by the
+ -- Replace internal identifier of rewritten node by the
-- identifier found in the sources. We also have to exchange
-- entities containing their defining identifiers to ensure
-- the correct replacement of the object declaration by this
-- wrapper functions for each nonoverridden inherited function
-- with a controlling result of the type. The wrapper for such
-- a function returns an extension aggregate that invokes the
- -- the parent function.
+ -- parent function.
if Ada_Version >= Ada_2005
and then not Is_Abstract_Type (Def_Id)
-- in packages System.Concat_n.
Known_Non_Null_Operand_Seen : Boolean;
- -- Set True during generation of the assignements of operands into
+ -- Set True during generation of the assignments of operands into
-- result once an operand known to be non-null has been seen.
function Make_Artyp_Literal (Val : Nat) return Node_Id;
-- We can't just use the index type, or even its base type for this
-- purpose for two reasons. First it might be an enumeration type which
- -- is not suitable fo computations of any kind, and second it may simply
- -- not have enough range. For example if the index type is -128..+127
- -- then lengths can be up to 256, which is out of range of the type.
+ -- is not suitable for computations of any kind, and second it may
+ -- simply not have enough range. For example if the index type is
+ -- -128..+127 then lengths can be up to 256, which is out of range of
+ -- the type.
-- For enumeration types, we can simply use Standard_Integer, this is
-- sufficient since the actual number of enumeration literals cannot
-- Same if the allocator is an access discriminant for a local object:
-- instead of an allocator we create a local value and constrain the
- -- the enclosing object with the corresponding access attribute.
+ -- enclosing object with the corresponding access attribute.
if Is_Static_Coextension (N) then
Rewrite_Coextension (N);
-- raise Storage_Error;
-- end if;
- -- where 3.5 gigabytes is a constant large enough to accomodate any
+ -- where 3.5 gigabytes is a constant large enough to accommodate any
-- reasonable request for. But we can't do it this way because at
-- least at the moment we don't compute this attribute right, and
-- can silently give wrong results when the result gets large. Since
-- Cnn := else-expr'Unrestricted_Access;
-- end if;
- -- and replace the conditional expresion by a reference to Cnn.all.
+ -- and replace the conditional expression by a reference to Cnn.all.
-- This special case can be skipped if the back end handles limited
-- types properly and ensures that no incorrect copies are made.
-- Start of processing for Expand_N_In
begin
- -- If set membersip case, expand with separate procedure
+ -- If set membership case, expand with separate procedure
if Present (Alternatives (N)) then
Remove_Side_Effects (Lop);
-- target is a real type or a 64-bit integer type, and the operand
-- is an arithmetic operation using a 32-bit integer type. However,
-- we do not bother with this case, because it could cause significant
- -- ineffiencies on 32-bit machines. On a 64-bit machine it would be
+ -- inefficiencies on 32-bit machines. On a 64-bit machine it would be
-- much cheaper, but we don't want different behavior on 32-bit and
-- 64-bit machines. Note that the exclusion of the 64-bit case also
-- handles the configurable run-time cases where 64-bit arithmetic
end if;
-- Reset the Analyzed flag, because the bounds of the index
- -- type itself may be universal, and must must be reaanalyzed
+ -- type itself may be universal, and must must be reanalyzed
-- to acquire the proper type for the back end.
Set_Analyzed (Cleft_Lo, False);
-- Note: the expander can handle generation of loops over predicated
-- subtypes for both the dynamic and static cases. Depending on what
- -- we decide is allowed in Ada 2012 mode and/or extentions allowed
+ -- we decide is allowed in Ada 2012 mode and/or extensions allowed
-- mode, the semantic analyzer may disallow one or both forms.
procedure Expand_Predicated_Loop (N : Node_Id) is
-- Ada 2005 (AI-231): Check null-excluding access types. Note that
-- the intent of 6.4.1(13) is that null-exclusion checks should
-- not be done for 'out' parameters, even though it refers only
- -- to constraint checks, and a null_exlusion is not a constraint.
+ -- to constraint checks, and a null_exclusion is not a constraint.
-- Note that AI05-0196-1 corrects this mistake in the RM.
if Is_Access_Type (Etype (Formal))
-- Functions returning controlled objects need special attention:
-- if the return type is limited, the context is an initialization
-- and different processing applies. If the call is to a protected
- -- function, the expansion above will call Expand_Call recusively.
+ -- function, the expansion above will call Expand_Call recursively.
-- To prevent a double attachment, check that the current call is
-- not a rewriting of a protected function call.
---------------------------
-- The Deep procedures call the appropriate Controlling proc on the
- -- the controller component. In the init case, it also attach the
+ -- controller component. In the init case, it also attach the
-- controller to the current finalization list.
function Make_Deep_Record_Body
-- ??? We want to migrate all platforms to use the same convention. As a
-- first step, we force this constant to always be True. This constant will
-- eventually be deleted after we have verified that the migration does not
- -- cause any unforseen adverse impact. We chose "__" because it is
+ -- cause any unforeseen adverse impact. We chose "__" because it is
-- supported on all platforms, which is not the case of "$".
procedure Get_External_Name
Parent (Entity (Prefix (Controlling_Tag))));
-- For a direct reference of the tag of the type the SCIL node
- -- references the the internal object declaration containing the tag
+ -- references the internal object declaration containing the tag
-- of the type.
elsif Nkind (Controlling_Tag) = N_Attribute_Reference
-- excluded from this check because interfaces must be visible in
-- the public and private part (RM 7.3 (7.3/2))
- -- We disable this check in CodePeer mode, to accomodate legacy
+ -- We disable this check in CodePeer mode, to accommodate legacy
-- Ada code.
if not CodePeer_Mode
procedure Expand_Multiply_Integer_By_Fixed_Giving_Fixed (N : Node_Id);
-- This routine expands the multiplication between standard integer and a
-- fixed-point type. The result type is the same fixed-point type as the
- -- the fixed operand type. N is an N_Op_Multiply node whose result type
+ -- fixed operand type. N is an N_Op_Multiply node whose result type
-- and right operand types are the fixed-point type, and whose left operand
-- type is always standard integer.
(not In_Same_Source_Unit (Renamed_Subp, Ent)
or else Sloc (Renamed_Subp) < Sloc (Ent))
- -- We can make the renaming entity intrisic if the renamed function
+ -- We can make the renaming entity intrinsic if the renamed function
-- has an interface name, or if it is one of the shift/rotate
-- operations known to the compiler.
return False;
-- A subtype of a variant record must not have non-static
- -- discriminanted components.
+ -- discriminated components.
elsif T /= Base_Type (T)
and then not Static_Discriminated_Components (T)
-- Deal with delayed aspect specifications. At the point of occurrence
-- of the aspect definition, we preanalyzed the argument, to capture
-- the visibility at that point, but the actual analysis of the aspect
- -- is required to be delayed to the freeze point, so we evalute the
+ -- is required to be delayed to the freeze point, so we evaluate the
-- pragma or attribute definition clause in the tree at this point.
if Has_Delayed_Aspects (E) then
end if;
end if;
- -- Give warning for suspicous return of a result of an
+ -- Give warning for suspicious return of a result of an
-- unconstrained array type in a foreign convention
-- function.
else
-- We used to check here that a full type must have preelaborable
-- initialization if it completes a private type specified with
- -- pragma Preelaborable_Intialization, but that missed cases where
+ -- pragma Preelaborable_Initialization, but that missed cases where
-- the types occur within a generic package, since the freezing
-- that occurs within a containing scope generally skips traversal
-- of a generic unit's declarations (those will be frozen within
-- additional facilities.
-- The identification of the low level interface is directly inspired by the
--- the base API organization, basically consisting of a rich set of functions
+-- base API organization, basically consisting of a rich set of functions
-- around a core of low level primitives mapping to AltiVec instructions.
-- See for instance "vec_add" in [PIM-4.4 Generic and Specific AltiVec
-- Display_Help (Config);
-- that will display a properly formatted help message for your application,
-- listing all possible switches. That way you have a single place in which
--- to maintain the list of switches and their meaning, rather than maintaing
+-- to maintain the list of switches and their meaning, rather than maintaining
-- both the string to pass to Getopt and a subprogram to display the help.
-- Both will properly stay synchronized.
package GNAT.Exception_Actions is
type Exception_Action is access
- procedure (Occurence : Exception_Occurrence);
+ procedure (Occurrence : Exception_Occurrence);
-- General callback type whenever an exception is raised. The callback
-- procedure must not propagate an exception (execution of the program
-- is erroneous if such an exception is propagated).
-- One might assume that we could get a more accurate result by testing
-- the lower and upper bounds of the type Rst against the bounds of 32-bit
-- Integer. However, there is no easy way to do that. Why? Because in the
- -- relatively rare case where this expresion has to be evaluated at run
+ -- relatively rare case where this expression has to be evaluated at run
-- time rather than compile time (when the bounds are dynamic), we need a
-- type to use for the computation. But the possible range of upper bound
-- values for Rst (remembering the possibility of 64-bit modular types) is
-- --
------------------------------------------------------------------------------
--- This package provides common suporting code for a family of secure
+-- This package provides common supporting code for a family of secure
-- hash functions (including MD5 and the FIPS PUB 180-3 functions SHA-1,
-- SHA-224, SHA-256, SHA-384 and SHA-512).
------------------------------------------------------------------------------
-- This package provides supporting code for implementation of the SHA-1
--- secure hash function as decsribed in FIPS PUB 180-3. The complete text
+-- secure hash function as described in FIPS PUB 180-3. The complete text
-- of FIPS PUB 180-3 can be found at:
-- http://csrc.nist.gov/publications/fips/fips180-3/fips180-3_final.pdf
-- --
------------------------------------------------------------------------------
--- This package implaments the SHA-1 secure hash function as decsribed in
+-- This package implements the SHA-1 secure hash function as described in
-- FIPS PUB 180-3. The complete text of FIPS PUB 180-3 can be found at:
-- http://csrc.nist.gov/publications/fips/fips180-3/fips180-3_final.pdf
-- --
------------------------------------------------------------------------------
--- This package implaments the SHA-224 secure hash function as decsribed in
+-- This package implements the SHA-224 secure hash function as described in
-- FIPS PUB 180-3. The complete text of FIPS PUB 180-3 can be found at:
-- http://csrc.nist.gov/publications/fips/fips180-3/fips180-3_final.pdf
-- --
------------------------------------------------------------------------------
--- This package implaments the SHA-256 secure hash function as decsribed in
+-- This package implements the SHA-256 secure hash function as described in
-- FIPS PUB 180-3. The complete text of FIPS PUB 180-3 can be found at:
-- http://csrc.nist.gov/publications/fips/fips180-3/fips180-3_final.pdf
-- --
------------------------------------------------------------------------------
--- This package implaments the SHA-384 secure hash function as decsribed in
+-- This package implements the SHA-384 secure hash function as described in
-- FIPS PUB 180-3. The complete text of FIPS PUB 180-3 can be found at:
-- http://csrc.nist.gov/publications/fips/fips180-3/fips180-3_final.pdf
-- --
------------------------------------------------------------------------------
--- This package implaments the SHA-512 secure hash function as decsribed in
+-- This package implements the SHA-512 secure hash function as described in
-- FIPS PUB 180-3. The complete text of FIPS PUB 180-3 can be found at:
-- http://csrc.nist.gov/publications/fips/fips180-3/fips180-3_final.pdf
-- --
------------------------------------------------------------------------------
--- This pacakge provides support for the 32-bit FIPS PUB 180-3 functions
+-- This package provides support for the 32-bit FIPS PUB 180-3 functions
-- SHA-224 and SHA-256.
-- This is an internal unit and should not be used directly in applications.
-- --
------------------------------------------------------------------------------
--- This pacakge provides support for the 64-bit FIPS PUB 180-3 functions
+-- This package provides support for the 64-bit FIPS PUB 180-3 functions
-- SHA-384 and SHA-512.
-- This is an internal unit and should not be used directly in applications.
end loop;
-- For an empty array, we have First > Max, and hence Index >= Max (no
- -- error, the loop above is never executed). After a succesful send,
+ -- error, the loop above is never executed). After a successful send,
-- Index = Max. The only remaining case, Index < Max, is therefore
-- always an actual send failure.
-- Sockets are designed to provide a consistent communication facility
-- between applications. This package provides an Ada binding to the
- -- the de-facto standard BSD sockets API. The documentation below covers
+ -- de-facto standard BSD sockets API. The documentation below covers
-- only the specific binding provided by this package. It assumes that
-- the reader is already familiar with general network programming and
-- sockets usage. A useful reference on this matter is W. Richard Stevens'
-- - thread unsafe.
--
-- In the first and third cases, the Buf and Buflen are ignored. In the
- -- second case, the caller must provide a buffer large enough to accomodate
- -- the returned data. In the third case, the caller must ensure that these
- -- functions are called within a critical section.
+ -- second case, the caller must provide a buffer large enough to
+ -- accommodate the returned data. In the third case, the caller must ensure
+ -- that these functions are called within a critical section.
function C_Gethostbyname
(Name : C.char_array;
static void finish_fat_pointer_type (tree, tree);
/* The relevant constituents of a subprogram binding to a GCC builtin. Used
- to pass around calls performing profile compatibilty checks. */
+ to pass around calls performing profile compatibility checks. */
typedef struct {
Entity_Id gnat_entity; /* The Ada subprogram entity. */
{
gnu_builtin_decl = builtin_decl_for (gnu_ext_name);
- /* Unability to find the builtin decl most often indicates a
+ /* Inability to find the builtin decl most often indicates a
genuine mistake, but imports of unregistered intrinsics are
sometimes issued on purpose to allow hooking in alternate
bodies. We post a warning conditioned on Wshadow in this case,
compatible. Issue relevant warnings when they are not.
This is intended as a light check to diagnose the most obvious cases, not
- as a full fledged type compatiblity predicate. It is the programmer's
+ as a full fledged type compatibility predicate. It is the programmer's
responsibility to ensure correctness of the Ada declarations in Imports,
especially when binding straight to a compiler internal. */
required if this is a static expression because it might be used
in a context where a dereference is inappropriate, such as a case
statement alternative or a record discriminant. There is no possible
- volatile-ness short-circuit here since Volatile constants must bei
+ volatile-ness short-circuit here since Volatile constants must be
imported per C.6. */
if (Ekind (gnat_temp) == E_Constant
&& Is_Scalar_Type (gnat_temp_type)
case MULT_EXPR:
/* The check here is designed to be efficient if the rhs is constant,
but it will work for any rhs by using integer division.
- Four different check expressions determine wether X * C overflows,
+ Four different check expressions determine whether X * C overflows,
depending on C.
C == 0 => false
C > 0 => X > type_max / C || X < type_min / C
if (TREE_CONSTANT (exp) || code == SAVE_EXPR || code == NULL_EXPR)
return exp;
- /* If EXP has no side effects, we theoritically don't need to do anything.
+ /* If EXP has no side effects, we theoretically don't need to do anything.
However, we may be recursively passed more and more complex expressions
involving checks which will be reused multiple times and eventually be
unshared for gimplification; in order to avoid a complexity explosion
Targparm.Frontend_Layout_On_Target := True;
end if;
- -- Set and check exception mechnism
+ -- Set and check exception mechanism
if Targparm.ZCX_By_Default_On_Target then
if Targparm.GCC_ZCX_Support_On_Target then
@noindent
This is an Ada 2012 representation pragma which applies to protected, task
and synchronized interface primitives. The use of pragma Implemented provides
-a way to impose a static requirement on the overriding opreration by adhering
+a way to impose a static requirement on the overriding operation by adhering
to one of the three implementation kids: entry, protected procedure or any of
the above.
@noindent
When applied to the procedure_or_entry_NAME of a requeue statement, pragma
Implemented determines the runtime behavior of the requeue. Implementation kind
-By_Entry guarantees that the action of requeueing will procede from an entry to
+By_Entry guarantees that the action of requeueing will proceed from an entry to
another entry. Implementation kind By_Protected_Procedure transforms the
requeue into a dispatching call, thus eliminating the chance of blocking. Kind
By_Any shares the behavior of By_Entry and By_Protected_Procedure depending on
@noindent
Without a pragma Pack, each Boolean field requires 8 bits, so the
minimum size is 72 bits, but with a pragma Pack, 16 bits would be
-sufficient. The use of pragma Implciit_Packing allows this record
+sufficient. The use of pragma Implicit_Packing allows this record
declaration to compile without an explicit pragma Pack.
@node Pragma Import_Exception
@unnumberedsec Pragma Import_Exception
an entity thus marked that the subprogram is obsolescent if the appropriate
warning option in the compiler is activated. If the Message parameter is
present, then a second warning message is given containing this text. In
-addition, a reference to the eneity is considered to be a violation of pragma
+addition, a reference to the entity is considered to be a violation of pragma
Restrictions (No_Obsolescent_Features).
This pragma can also be used as a program unit pragma for a package,
exists, Copy_File fails.
@item overwrite
-Copy the file in all cases. Overwite an already existing destination file.
+Copy the file in all cases. Overwrite an already existing destination file.
@item append
Append the original file to the destination file. If the destination file does
machines that are not fully compliant with this standard, such as Alpha, the
@option{-mieee} compiler flag must be used for achieving IEEE confirming
behavior (although at the cost of a significant performance penalty), so
-infinite and and NaN values are properly generated.
+infinite and NaN values are properly generated.
@node Implementation of Ada 2012 Features
@cindex AI-0003 (Ada 2012 feature)
@noindent
- In Ada 2012, a qualified expression is considered to be syntatically a name,
+ In Ada 2012, a qualified expression is considered to be syntactically a name,
meaning that constructs such as @code{A'(F(X)).B} are now legal. This is
useful in disambiguating some cases of overloading.
@noindent
This AI covers a number of issues regarding returning abstract types. In
- particular generic fucntions cannot have abstract result types or access
+ particular generic functions cannot have abstract result types or access
result types designated an abstract type. There are some other cases which
are detailed in the AI. Note that this binding interpretation has not been
retrofitted to operate before Ada 2012 mode, since it caused a significant
@item
-@emph{AI-0050 Raising Constraingt_Errpr early for function call (0000-00-00)}
+@emph{AI-0050 Raising Constraint_Error early for function call (0000-00-00)}
@cindex AI-0050 (Ada 2012 feature)
@noindent
- The implementation permissions for raising @code{Constraing_Error} early on a function call when it was clear an exception would be raised were over-permissive and allowed mishandling of discriminants in some cases. GNAT did
+ The implementation permissions for raising @code{Constraint_Error} early on a function call when it was clear an exception would be raised were over-permissive and allowed mishandling of discriminants in some cases. GNAT did
not take advantage of these incorrect permissions in any case.
@noindent
@noindent
This AI clarifies that ``needs finalization'' is part of dynamic semantics,
- and therefore depends on the run-time charateristics of an object (i.e. its
+ and therefore depends on the run-time characteristics of an object (i.e. its
tag) and not on its nominal type. As the AI indicates: ``we do not expect
this to affect any implementation''.
forbid tasks declared locally within subprograms, or functions returning task
objects, and that is the implementation that GNAT has always provided.
However the language in the RM was not sufficiently clear on this point.
- Thus this is a docmentation change in the RM only.
+ Thus this is a documentation change in the RM only.
@noindent
RM References: D.07 (3/3)
Note that @option{-gnatwa} does not affect the setting of this warning option.
@item -gnatw.S
-@emph{Suppress warnings on overriddebn size clauses.}
+@emph{Suppress warnings on overridden size clauses.}
@cindex @option{-gnatw.S} (@command{gcc})
This switch suppresses warnings on component clauses in record
representation clauses that override size clauses, and similar
For further details see @ref{Dynamic Allocation Control}.
@item ^-H64^/64_MALLOC^
-@cindex @option{^-H32^/32_MALLOC^} (@command{gnatbind})
+@cindex @option{^-H64^/64_MALLOC^} (@command{gnatbind})
Use 64-bit allocations for @code{__gnat_malloc} (and thus for access types).
@cindex @code{__gnat_malloc}
For further details see @ref{Dynamic Allocation Control}.
instance that you do not have a directory called "sources.ads" when using the
default GNAT naming scheme).
-When you do not have to use this switch (ie by default), gnatmake is able to
+When you do not have to use this switch (i.e.@: by default), gnatmake is able to
save a lot of system calls (several per source file and object file), which
can result in a significant speed up to load and manipulate a project file,
especially when using source files from a remote system.
@item ^-O3^/OPTIMIZE=INLINING^
Full optimization as in @option{-O2};
also uses more aggressive automatic inlining of subprograms within a unit
-(@pxref{Inlining of Subprograms}) and attemps to vectorize loops.
+(@pxref{Inlining of Subprograms}) and attempts to vectorize loops.
@item ^-Os^/OPTIMIZE=SPACE^
Optimize space usage (code and data) of resulting program.
@item ^-wq^/WARNINGS=QUIET^
@cindex @option{^-wq^/WARNINGS=QUIET^} (@command{gnatelim})
-Quet warning mode - some warnings are suppressed. In particular warnings that
+Quiet warning mode - some warnings are suppressed. In particular warnings that
indicate that the analysed set of sources is incomplete to make up a
partition and that some subprogram bodies are missing are not generated.
@end table
@item ^--subdirs^/SUBDIRS^=subdir
Actual object directory of each project file is the subdirectory subdir of the
-object directory specified or defauted in the project file.
+object directory specified or defaulted in the project file.
@item ^--unchecked-shared-lib-imports^/UNCHECKED_SHARED_LIB_IMPORTS^
By default, shared library projects are not allowed to import static library
@item ^--no-exception^/NO_EXCEPTION^
@cindex @option{^--no-exception^/NO_EXCEPTION^} (@command{gnatstub})
-Avoind raising PROGRAM_ERROR in the generated bodies of program unit stubs.
+void raising PROGRAM_ERROR in the generated bodies of program unit stubs.
This is not always possible for function stubs.
@item ^--no-local-header^/NO_LOCAL_HEADER^
The binding generator is part of the @command{gcc} compiler and can be
invoked via the @option{-fdump-ada-spec} switch, which will generate Ada
spec files for the header files specified on the command line, and all
-header files needed by these files transitivitely. For example:
+header files needed by these files transitively. For example:
@smallexample
$ g++ -c -fdump-ada-spec -C /usr/include/time.h
raises the exception @var{name}.
@item catch exception unhandled
-Set a catchpoint that stops executino whenever (any task in the) program
+Set a catchpoint that stops executing whenever (any task in the) program
raises an exception for which there is no handler.
@item info exceptions
@end enumerate
The first three are the GNU style import libraries. The third is the
-Microsoft style import libraries. The last two are the DLL themself.
+Microsoft style import libraries. The last two are the actual DLL names.
Note that if the Ada package spec for @file{API.dll} contains the
following pragma
That predicate function is called indirectly, via a function pointer,
by __gnat_error_handler, and changing that pointer is allowed to the
- the user code by way of the __gnat_set_resignal_predicate interface.
+ user code by way of the __gnat_set_resignal_predicate interface.
The user level function may then implement what it likes, including
for instance the maintenance of a dynamic data structure if the set
function Process (N : Node_Id) return Traverse_Result;
-- Look for calls to subprograms with no previous spec, declared
- -- in the same enclosiong package body.
+ -- in the same enclosing package body.
-------------
-- Process --
/* be used by default for linking libgnat (shared or static) */
/* shared_libgcc_default gives the system dependent link method that */
-/* be used by default for linking libgcc (shared or statis) */
+/* be used by default for linking libgcc (shared or static) */
/* using_gnu_linker is set to 1 when the GNU linker is used under this */
/* target. */
/*
c_get_language_code needs to fill in the Alpha-3 encoding of the
- language code (3 lowercase letters). That shoud be "und" if the
+ language code (3 lowercase letters). That should be "und" if the
language is unknown. [see Ada.Locales]
*/
void c_get_language_code (char4 p) {
/*
c_get_country_code needs to fill in the Alpha-2 encoding of the
- country code (2 uppercase letters). That shoud be "ZZ" if the
+ country code (2 uppercase letters). That should be "ZZ" if the
country is unknown. [see Ada.Locales]
*/
void c_get_country_code (char4 p) {
-- extracted.
function Processed return Natural;
- -- Return the number of source in the queue that have aready been
+ -- Return the number of source in the queue that have already been
-- processed.
procedure Set_Obj_Dir_Busy (Obj_Dir : Path_Name_Type);
end;
end if;
- -- Add switch -M to gnatlink if buider switch --create-map-file
- -- has been specified.
+ -- Add switch -M to gnatlink if builder switch
+ -- --create-map-file has been specified.
if Map_File /= null then
Linker_Switches.Increment_Last;
-- If Put_In_Q is False, we add the source as if it were specified
-- on the command line, and we set Put_In_Q to True, so that the
-- following sources will only be put in the queue. The source is
- -- aready in the Q, but we need at least one fake main to call
+ -- already in the Q, but we need at least one fake main to call
-- Compile_Sources.
if Verbose_Mode then
extern UINT CurrentCodePage;
-/* Macros to convert to/from the code page speficied in CurrentCodePage. */
+/* Macros to convert to/from the code page specified in CurrentCodePage. */
#define S2WSC(wstr,str,len) \
MultiByteToWideChar (CurrentCodePage,0,str,-1,wstr,len)
#define WS2SC(str,wstr,len) \
-- initialization is performed automatically during package elaboration.
-- Note that this change fixes problems which existed prior to the change
-- of Initialize being called more than once. See also Reinitialize which
- -- allows reinitialiation of the tables.
+ -- allows reinitialization of the tables.
procedure Lock;
-- Lock name tables before calling back end. We reserve some extra space
begin
-- If we are looking for a config file, look only in the current
-- directory, i.e. return input argument unchanged. Also look only in
- -- the curren directory if we are looking for a .dg file (happens in
+ -- the current directory if we are looking for a .dg file (happens in
-- -gnatD mode).
if T = Config
begin
-- Figure out if a generic actual part operation is present. Clearly
-- there is no generic actual part if the current token is semicolon
- -- or if we have apsect specifications present.
+ -- or if we have aspect specifications present.
if Token = Tok_Semicolon or else Aspect_Specifications_Present then
return No_List;
-- Parsed by P_Representation_Clause (13.1)
- ------------------------------
- -- 13.1 Aspect Specifation --
- ------------------------------
+ --------------------------------
+ -- 13.1 Aspect Specification --
+ --------------------------------
-- ASPECT_SPECIFICATION ::=
-- with ASPECT_MARK [=> ASPECT_DEFINITION] {.
if not Class_Aspect_OK (A_Id) then
Error_Msg_Node_1 := Identifier (Aspect);
Error_Msg_SC ("aspect& does not permit attribute here");
- Scan; -- past apostophe
+ Scan; -- past apostrophe
Scan; -- past presumed CLASS
OK := False;
else
-- In Ada 2012 mode, the expression must be a simple
- -- expression. The resaon for this restriction (i.e. going
+ -- expression. The reason for this restriction (i.e. going
-- back to the Ada 83 rule) is to avoid ambiguities when set
-- membership operations are allowed, consider the
-- following:
-- when A in 1 .. 10 | 12 =>
-- This is ambiguous without parentheses, so we require one
- -- of the following two parenthesized forms to disambuguate:
+ -- of the following two parenthesized forms to disambiguate:
-- one of the following:
Expr_Node := Error;
end Box_Error;
- -- Start of processsing for P_Aggregate_Or_Paren_Expr
+ -- Start of processing for P_Aggregate_Or_Paren_Expr
begin
Lparen_Sloc := Token_Ptr;
-- if it were a configuration pragma.
-- Since the reason we provide this pragma is for compatibility with
- -- these other compilers, we want to accomodate these strange placement
+ -- these other compilers, we want to accommodate these strange placement
-- rules, and the easiest thing is simply to allow it anywhere in a
-- unit. If this pragma appears anywhere within a unit, then the effect
-- is as though a pragma Suppress (All_Checks) had appeared as the first
Pbod : Boolean; -- True if proper body OK
Rnam : Boolean; -- True if renaming declaration OK
Stub : Boolean; -- True if body stub OK
- Pexp : Boolean; -- True if parametried expression OK
+ Pexp : Boolean; -- True if parametrized expression OK
Fil2 : Boolean; -- Filler to fill to 8 bits
end record;
pragma Pack (Pf_Rec);
function P_Range_Or_Subtype_Mark
(Allow_Simple_Expression : Boolean := False) return Node_Id;
-- Scans out a range or subtype mark, and also permits a general simple
- -- expression if Allow_Simple_Expresion is set to True.
+ -- expression if Allow_Simple_Expression is set to True.
function Init_Expr_Opt (P : Boolean := False) return Node_Id;
-- If an initialization expression is present (:= expression), then
-- of generating appropriate messages if aspect specifications appear
-- in versions of Ada prior to Ada 2012. The parameter strict can be
-- set to True, to be rather strict about considering something to be
- -- an aspect speficiation. If Strict is False, then the circuitry is
+ -- an aspect specification. If Strict is False, then the circuitry is
-- rather more generous in considering something ill-formed to be an
- -- attempt at an aspect speciciation. The default is more strict for
+ -- attempt at an aspect specification. The default is more strict for
-- Ada versions before Ada 2012 (where aspect specifications are not
-- permitted).
procedure Process_Decisions (N : Node_Id; T : Character);
-- If N is Empty, has no effect. Otherwise scans the tree for the node N,
-- to output any decisions it contains. T is one of IEPWX (for context of
- -- expresion: if/exit when/pragma/while/expression). If T is other than X,
+ -- expression: if/exit when/pragma/while/expression). If T is other than X,
-- the node N is the conditional expression involved, and a decision is
-- always present (at the very least a simple decision is present at the
-- top level).
-- The following variable should be a constant, but this is not possible
-- because its type GNAT.Dynamic_Tables.Instance has a component P of
- -- unitialized private type GNAT.Dynamic_Tables.Table_Private and there
+ -- uninitialized private type GNAT.Dynamic_Tables.Table_Private and there
-- are no exported values for this private type. Warnings are Off because
-- it is never assigned a value.
-- set).
--
-- If the processing fails, Main_Project is set to No_Project. If the error
- -- happend while parsing the project itself (ie creating the tree),
+ -- happened while parsing the project itself (i.e. creating the tree),
-- User_Project_Node is also set to Empty_Node.
--
-- Autoconf_Specified indicates whether the user has specified --autoconf.
-- by the user (either through gprbuild's --config or --autoconf switches).
-- In the latter case, Autoconf_Specified should be set to true to indicate
-- that the configuration file can be regenerated to match target and
- -- languages. This name can either be an absolute path, or the a base name
+ -- languages. This name can either be an absolute path, or the base name
-- that will be searched in the default config file directories (which
-- depends on the installation path for the tools).
--
Project : Project_Node_Id;
Attribute : Project_Node_Id;
Flags : Processing_Flags);
- -- Chech whether the attribute is valid in this project.
+ -- Check whether the attribute is valid in this project.
-- In particular, depending on the type of project (qualifier), some
-- attributes might be disabled.
-- Initial size of Buffer
Uninitialized_Prefix : constant String := '#' & Path_Separator;
- -- Prefix to indicate that the project path has not been initilized yet.
+ -- Prefix to indicate that the project path has not been initialized yet.
-- Must be two characters long
No_Project_Default_Dir : constant String := "-";
procedure Put (S : String);
procedure Put_Line (S : String);
-- Output procedures, analogous to normal Text_IO procs of same name.
- -- The text is put in Buffer, then it will be writen into a temporary
+ -- The text is put in Buffer, then it will be written into a temporary
-- file with procedure Write_Temp_File below.
procedure Write_Temp_File;
Project_File_Name : String;
Directory : String;
Path : out Namet.Path_Name_Type);
- -- Search for a the project with the given name either in Directory (which
+ -- Search for a project with the given name either in Directory (which
-- often will be the directory contain the project we are currently parsing
-- and which we found a reference to another project), or in the project
-- path. Extra_Project_Path contains additional directories to search.
end;
end if;
- -- Name_Buffer contains the name of the the unit in lower-cases. Check
+ -- Name_Buffer contains the name of the unit in lower-cases. Check
-- that this is a valid unit name
Check_Ada_Name (Name_Buffer (1 .. Name_Len), Unit);
-- error when appropriate
procedure Get_Sources_From_Source_Info;
- -- Get the source information from the tabes that were created when a
+ -- Get the source information from the tables that were created when a
-- source info fie was read.
---------------------------
To : Int);
pragma Inline (Set_Source_Index_Of);
-- Only valid for N_Literal_String and N_Attribute_Declaration nodes. For
- -- N_Literal_String, set the source index of the litteral string. For
+ -- N_Literal_String, set the source index of the literal string. For
-- N_Attribute_Declaration, set the source index of the index of the
-- associative array element.
External_References : Name_To_Name_HTable.Instance;
-- External references are stored in this hash table (and manipulated
- -- through subprogrames in prj-ext.ads). External references are
+ -- through subprograms in prj-ext.ads). External references are
-- project-tree specific so that one can load the same tree twice but
-- have two views of it, for instance.
-- Open a text file to read (File is invalid if text file cannot be opened)
procedure Create (File : out Text_File; Name : String);
- -- Create a text file to write (File is invaid if text file cannot be
+ -- Create a text file to write (File is invalid if text file cannot be
-- created).
function End_Of_File (File : Text_File) return Boolean;
procedure Initialize
(Iter : out Source_Info_Iterator;
For_Project : Name_Id);
- -- Initiaize Iter for the project
+ -- Initialize Iter for the project
function Source_Info_Of (Iter : Source_Info_Iterator) return Source_Info;
-- Get the source info for the source corresponding to the current value of
or else Source.Kind /= Spec)
then
-- Do not modify Source.Compilable before the source record
- -- has been initilaized.
+ -- has been initialized.
if Source.Source_TS /= Empty_Time_Stamp then
Source.Compilable := Yes;
-- Return the object directory to use for the project. This depends on
-- whether we have a library project or a standard project. This function
-- might return No_Name when no directory applies.
- -- If we have a a library project file and Including_Libraries is True then
+ -- If we have a library project file and Including_Libraries is True then
-- the library dir is returned instead of the object dir.
-- If Only_If_Ada is True, then No_Name will be returned when the project
-- doesn't Ada sources.
type Error_Handler is access procedure
(Project : Project_Id;
Is_Warning : Boolean);
- -- This warngs when an error was found when parsing a project. The error
+ -- This warns when an error was found when parsing a project. The error
-- itself is handled through Prj.Err (and Prj.Err.Finalize should be called
-- to actually print the error). This ensures that duplicate error messages
-- are always correctly removed, that errors msgs are sorted, and that all
project.
Note that it is considered an error for a project file to have no sources
-attached to it unless explicitly declared as mentionend above.
+attached to it unless explicitly declared as mentioned above.
If the order of the source directories is known statically, that is if
@code{"/**"} is not used in the string list @code{Source_Dirs}, then there may
We now have a project file that fully describes our environment, and can be
used to build the application with a simple @command{gnatmake} command as seen
in the previous section. In fact, the empty project we showed immediately at
-the beginning (with no attribute at all) could already fullfill that need if it
+the beginning (with no attribute at all) could already fulfill that need if it
was put in the @file{common} directory.
Of course, we always want more control. This section will show you how to
The default output of GPRbuild's execution is kept reasonably simple and easy
to understand. In particular, some of the less frequently used commands are not
shown, and some parameters are abbreviated. So it is not possible to rerun the
-effect ofthe gprbuild command by cut-and-pasting its output. GPRbuild's option
+effect of the gprbuild command by cut-and-pasting its output. GPRbuild's option
@code{-v} provides a much more verbose output which includes, among other
information, more complete compilation, post-compilation and link commands.
using attribute @code{Source_Files} or equivalent. By contrast, 2 projects
can each own a source with the same base file name as long as they live in
different directories. The latter is not true for Ada Sources because of the
-correlation betwen source files and Ada units.
+correlation between source files and Ada units.
@c ---------------------------------------------
@node Cyclic Project Dependencies
@c ---------------------------------------------
@noindent
-When building an application, it is common to have similar needs in severa of
+When building an application, it is common to have similar needs in several of
the projects corresponding to the subsystems under construction. For instance,
they will all have the same compilation switches.
@noindent
Let's enhance our example and transform the @code{logging} subsystem into a
-library.In orer to do so, a few changes need to be made to @file{logging.gpr}.
+library. In order to do so, a few changes need to be made to @file{logging.gpr}.
A number of specific attributes needs to be defined: at least @code{Library_Name}
and @code{Library_Dir}; in addition, a number of other attributes can be used
-to specify specific aspects of the library. For readablility, it is also
+to specify specific aspects of the library. For readability, it is also
recommended (although not mandatory), to use the qualifier @code{library} in
front of the @code{project} keyword.
which kind of library should be build (the default is to build a
static library, that is an archive of object files that can potentially
be linked into a static executable). When the library is set to be dynamic,
- a separate image is created that will be loaded independnently, usually
+ a separate image is created that will be loaded independently, usually
at the start of the main program execution. Support for dynamic libraries is
very platform specific, for instance on Windows it takes the form of a DLL
while on GNU/Linux, it is a dynamic elf image whose suffix is usually
@file{.so}. Library project files, on the other hand, can be written in
- a platform independant way so that the same project file can be used to build
- a library on different Oses.
+ a platform independent way so that the same project file can be used to build
+ a library on different operating systems.
If you need to build both a static and a dynamic library, it is recommended
use two different object directories, since in some cases some extra code
It is also possible to build @b{multi-language libraries}. When using
@command{gprbuild} as a builder, multi-language library projects allow naturally
-the creation of multi-language libraries . @command{gnatmake}, does n ot try to
+the creation of multi-language libraries . @command{gnatmake}, does not try to
compile non Ada sources. However, when the project is multi-language, it will
automatically link all object files found in the object directory, whether or
not they were compiled from an Ada source file. This specific behavior does not
library is a convenient way to add an Ada subsystem to a more global system
whose main is not in Ada since it makes the elaboration of the Ada part mostly
transparent. However, stand-alone libraries are also useful when the main is in
-Ada: they provide a means for minimizing relinking & redeployement of complex
+Ada: they provide a means for minimizing relinking & redeployment of complex
systems when localized changes are made.
-The most proeminent characteristic of a stand-alone library is that it offers a
+The most prominent characteristic of a stand-alone library is that it offers a
distinction between interface units and implementation units. Only the former
are visible to units outside the library. A stand-alone library project is thus
characterised by a third attribute, @b{Library_Interface}, in addition to the
This project name must be present after the reserved
word @code{end} at the end of the project file, followed by a semi-colon.
-@b{Identifiers} (ie the user-defined names such as project or variable names)
+@b{Identifiers} (i.e.@: the user-defined names such as project or variable names)
have the same syntax as Ada identifiers: they must start with a letter,
and be followed by zero or more letters, digits or underscore characters;
it is also illegal to have two underscores next to each other. Identifiers
@noindent
An expression is any value that can be assigned to an attribute or a
-variable. It is either a litteral value, or a construct requiring runtime
+variable. It is either a literal value, or a construct requiring runtime
computation by the project manager. In a project file, the computed value of
an expression is either a string or a list of strings.
empty string or if the external value is only one separator.
Any separator at the beginning or at the end of the external value is
-discarded. Then, if there is no separator in the external vaue, the result is
-a string list with only one string. Otherwise, any string between the biginning
+discarded. Then, if there is no separator in the external value, the result is
+a string list with only one string. Otherwise, any string between the beginning
and the first separator, between two consecutive separators and between the
last separator and the end are components of the string list.
@item Object_File_Suffix @tab string @tab Compiler @tab insensitive (language)
@item Object_File_Switches @tab list @tab Compiler @tab insensitive (language)
@item Multi_Unit_Switches @tab list @tab Compiler @tab insensitive (language)
-@item Multi_Unit_Object_Separator @tab string @tab Compiler @tab insensitve (language)
+@item Multi_Unit_Object_Separator @tab string @tab Compiler @tab insensitive (language)
@item Mapping_File_Switches @tab list @tab Compiler @tab insensitive (language)
@item Mapping_Spec_Suffix @tab string @tab Compiler @tab insensitive (language)
@item Mapping_body_Suffix @tab string @tab Compiler @tab insensitive (language)
will compute the metrics for the closure of units rooted at
@code{main_unit}. This last possibility relies implicitly
on @command{gnatbind}'s option @option{-R}. But if the argument files for the
-tool invoked by the the @command{gnat} driver are explicitly specified
+tool invoked by the @command{gnat} driver are explicitly specified
either directly or through the tool @option{-files} option, then the tool
is called only for these explicitly specified files.
Old_Bit : Boolean;
begin
- -- All these ASM sequences should be commented. I suggest definining
+ -- All these ASM sequences should be commented. I suggest defining
-- a constant called E which is LF & HT and then you have more space
-- for line by line comments ???
Mechanism => (Reference, Value, Value, Reference, Reference));
pragma Inline_Always (Or_Atomic);
- -- Inline the VAX Queue Funtions
+ -- Inline the VAX Queue Functions
pragma Inline_Always (Insqhi);
pragma Inline_Always (Remqhi);
#endif
/**
- ** Tru64 UNIX V4.0F defines AF_INET6 without IPv6 support, specificially
+ ** Tru64 UNIX V4.0F defines AF_INET6 without IPv6 support, specifically
** without struct sockaddr_in6. We use _SS_MAXSIZE (used for the definition
** of struct sockaddr_storage on Tru64 UNIX V5.1) to detect this.
**/
Handler : Interrupt_Handler;
Parameter : System.Address := System.Null_Address) return int;
pragma Inline (Interrupt_Connect);
- -- Use this to set up an user handler. The routine installs a a user
+ -- Use this to set up an user handler. The routine installs a user
-- handler which is invoked after the OS has saved enough context for a
-- high-level language routine to be safely invoked.
GetSystemTimeAsFileTime (Ctrl_Time'Access);
- -- Scan for clock tick, will take upto 16ms/1ms depending on PC.
+ -- Scan for clock tick, will take up to 16ms/1ms depending on PC.
-- This cannot be an infinite loop or the system hardware is badly
- -- dammaged.
+ -- damaged.
loop
GetSystemTimeAsFileTime (Loc_Time'Access);
Past_Elmt : Boolean := False;
-- Set to True everywhere an elmt has been parsed, if Glob=False,
- -- meaning there can be now an occurence of '*', '+' and '?'.
+ -- meaning there can be now an occurrence of '*', '+' and '?'.
Past_Term : Boolean := False;
-- Set to True everywhere a term has been parsed, if Glob=False,
- -- meaning there can be now an occurence of '|'.
+ -- meaning there can be now an occurrence of '|'.
Parenthesis_Level : Integer := 0;
Curly_Level : Integer := 0;
Last_Open : Integer := S'First - 1;
- -- The last occurence of an opening parenthesis, if Glob=False,
- -- or the last occurence of an opening curly brace, if Glob=True.
+ -- The last occurrence of an opening parenthesis, if Glob=False,
+ -- or the last occurrence of an opening curly brace, if Glob=True.
procedure Raise_Exception_If_No_More_Chars (K : Integer := 0);
-- If no more characters are raised, call Raise_Exception
-- System.Stack_Usage.Result_Array
procedure Compute_Current_Task;
- -- Compute the stack usage for a given task and saves it in the a precise
+ -- Compute the stack usage for a given task and saves it in the precise
-- slot in System.Stack_Usage.Result_Array;
procedure Report_Impl (All_Tasks : Boolean; Do_Print : Boolean);
if T.Common.Base_CPU /= System.Multiprocessors.Not_A_Specific_CPU then
-- The CPU numbering in pragma CPU starts at 1 while the subprogram
- -- to set the affinity starts at 0, therefore we must substract 1.
+ -- to set the affinity starts at 0, therefore we must subtract 1.
Result := SetThreadIdealProcessor
(hTask, ProcessorId (T.Common.Base_CPU) - 1);
System.Multiprocessors.Not_A_Specific_CPU
then
-- The CPU numbering in pragma CPU starts at 1 while the subprogram
- -- to set the affinity starts at 0, therefore we must substract 1.
+ -- to set the affinity starts at 0, therefore we must subtract 1.
Result :=
SetThreadIdealProcessor
System.Multiprocessors.Not_A_Specific_CPU
then
-- The CPU numbering in pragma CPU starts at 1 while the subprogram
- -- to set the affinity starts at 0, therefore we must substract 1.
+ -- to set the affinity starts at 0, therefore we must subtract 1.
Result :=
processor_bind
if not Used_As_Identifier (Token) or else Force_Msg then
- -- If "some" is made into a reseverd work in Ada2012, the following
- -- check will make it into a regular identifer in earlier versions
+ -- If "some" is made into a reserved work in Ada2012, the following
+ -- check will make it into a regular identifier in earlier versions
-- of the language.
if Token = Tok_Some and then Ada_Version < Ada_2012 then
-- operand of a logical operator.
-- Decisions are either simple or complex. A simple decision is a top
- -- level boolean expresssion that has only one condition and that occurs
+ -- level boolean expression that has only one condition and that occurs
-- in the context of a control structure in the source program, including
-- WHILE, IF, EXIT WHEN, or in an Assert, Check, Pre_Condition or
-- Post_Condition pragma. For pragmas, decision SCOs are generated only
Do_Withed_Units (CU, Include_Limited => False);
- -- Process the unit if it is a spec or the the main unit, if it
+ -- Process the unit if it is a spec or the main unit, if it
-- has no previous spec or we have done all other units.
if not Nkind_In (Item, N_Package_Body, N_Subprogram_Body)
-- for the rest, if other components are present.
-- The type of the aggregate is the known subtype of
-- the component. The capture of discriminants must
- -- be recursive because subcomponents may be contrained
+ -- be recursive because subcomponents may be constrained
-- (transitively) by discriminants of enclosing types.
-- For a private type with discriminants, a call to the
-- initialization procedure will be generated, and no
end if;
-- Check special case of Exception_Id and Exception_Occurrence which
- -- are not allowed for restriction No_Exception_Regstriation.
+ -- are not allowed for restriction No_Exception_Registration.
if Is_RTE (P_Type, RE_Exception_Id)
or else
-- only occur in the case of a _parent component anyway).
-- They don't have any components, plus it would cause this
-- function to return true for nonlimited types derived from
- -- limited intefaces.
+ -- limited interfaces.
if not Is_Interface (Etype (C))
and then Is_Immutably_Limited_Type (Etype (C))
-- the entity chain of the derived type which are a copy of the
-- discriminants of the root type. Furthermore their Is_Completely_Hidden
-- flag is set since although they are actually stored in the object, they
- -- are not in the set of discriminants that is visble in the type.
+ -- are not in the set of discriminants that is visible in the type.
--
-- For derived untagged types, the set of stored discriminants are the real
-- discriminants from Gigi's standpoint, i.e. those that will be stored in
-- These are the types that are defined as return-by-reference types in Ada
-- 95 (see RM95-6.5(11-16)). In Ada 2005, these are the types that require
-- build-in-place for function calls. Note that build-in-place is allowed
- -- for other types, too. This is also used for idenfitying pure procedures
+ -- for other types, too. This is also used for identifying pure procedures
-- whose calls should not be eliminated (RM 10.2.1(18/2)).
function Is_Limited_Type (Ent : Entity_Id) return Boolean;
-- Check restriction imposed by AI05-073: a generic function
-- cannot return an abstract type or an access to such.
- -- This is a binding interpreration should it apply to earlier
+ -- This is a binding interpretation should it apply to earlier
-- versions of Ada as well as Ada 2012???
if Is_Abstract_Type (Designated_Type (Result_Type))
-- the child unit that must be declared within. Similarly, if this is the
-- name of a generic child unit within an instantiation of its own parent,
-- retrieve the parent generic. If the parent is installed as a result of
- -- this call, then Parent_Installed is set True, otherwise Parent_Intalled
+ -- this call, then Parent_Installed is set True, otherwise Parent_Installed
-- is unchanged by the call.
function Copy_Generic_Node
procedure Build_Predicate_Function (Typ : Entity_Id; N : Node_Id);
-- If Typ has predicates (indicated by Has_Predicates being set for Typ,
-- then either there are pragma Invariant entries on the rep chain for the
- -- type (note that Predicate aspects are converted to pragam Predicate), or
+ -- type (note that Predicate aspects are converted to pragma Predicate), or
-- there are inherited aspects from a parent type, or ancestor subtypes.
-- This procedure builds the spec and body for the Predicate function that
-- tests these predicates. N is the freeze node for the type. The spec of
-- the function is inserted before the freeze node, and the body of the
- -- funtion is inserted after the freeze node.
+ -- function is inserted after the freeze node.
procedure Build_Static_Predicate
(Typ : Entity_Id;
-- whose predicate expression is Expr, tests if Expr is a static predicate,
-- and if so, builds the predicate range list. Nam is the name of the one
-- argument to the predicate function. Occurrences of the type name in the
- -- predicate expression have been replaced by identifer references to this
+ -- predicate expression have been replaced by identifier references to this
-- name, which is unique, so any identifier with Chars matching Nam must be
-- a reference to the type. If the predicate is non-static, this procedure
-- returns doing nothing. If the predicate is static, then the predicate
-- The entity of the object being overlaid
Off : Boolean;
- -- Whether the address is offseted within Y
+ -- Whether the address is offset within Y
end record;
package Address_Clause_Checks is new Table.Table (
end if;
-- Return if already analyzed (avoids duplicate calls in some cases
- -- where type declarations get rewritten and proessed twice).
+ -- where type declarations get rewritten and processed twice).
if Analyzed (N) then
return;
end if;
- -- Loop through apsects
+ -- Loop through aspects
Aspect := First (L);
while Present (Aspect) loop
end;
-- Invariant aspects generate a corresponding pragma with a
- -- first argument that is the entity, and the second argument
- -- is the expression and anthird argument with an appropriate
+ -- first argument that is the entity, a second argument that is
+ -- the expression and a third argument that is an appropriate
-- message. This is inserted right after the declaration, to
-- get the required pragma placement. The pragma processing
-- takes care of the required delay.
procedure Replace_Type_References is
new Replace_Type_References_Generic (Replace_Type_Reference);
-- Traverse an expression changing every occurrence of an identifier
- -- whose name mathches the name of the subtype with a reference to
+ -- whose name matches the name of the subtype with a reference to
-- the formal parameter of the predicate function.
----------------------------
function Is_False (R : RList) return Boolean;
pragma Inline (Is_False);
-- Returns True if the given range list is empty, and thus represents
- -- a False list of ranges that can never be satsified.
+ -- a False list of ranges that can never be satisfied.
function Is_True (R : RList) return Boolean;
-- Returns True if R trivially represents the True predicate by having
(N : Node_Id;
E : Entity_Id;
L : List_Id);
- -- This procedure is called to analyze aspect spefications for node N. E is
- -- the corresponding entity declared by the declaration node N, and L is
+ -- This procedure is called to analyze aspect specifications for node N. E
+ -- is the corresponding entity declared by the declaration node N, and L is
-- the list of aspect specifications for this node. If L is No_List, the
-- call is ignored. Note that we can't use a simpler interface of just
-- passing the node N, since the analysis of the node may cause it to be
-- This is called after the back end has been called (and thus after the
-- layout of components has been back annotated). It goes through the
-- table of saved pragma Independent[_Component] entries, checking that
- -- independence can be achieved, and if necessary issuing error mssags.
+ -- independence can be achieved, and if necessary issuing error messages.
-------------------------------------
-- Table for Validate_Independence --
Make_Pragma_Argument_Association (Loc,
Expression => Make_Identifier (Loc, Iface_Kind))));
- -- The pragma doesn't need to be analyzed because it is internaly
+ -- The pragma doesn't need to be analyzed because it is internally
-- build. It is safe to directly register it as a rep item since we
-- are only interested in the characters of the implementation kind.
"be allowed in Ada 2005?", S);
else
Error_Msg_N
- ("access subype of general access type not allowed", S);
+ ("access subtype of general access type not allowed", S);
end if;
Error_Msg_N ("\discriminants have defaults", S);
Access_Types_To_Process (Freeze_Node (Priv)));
end if;
- -- Swap the two entities. Now Privat is the full type entity and Full is
- -- the private one. They will be swapped back at the end of the private
- -- part. This swapping ensures that the entity that is visible in the
- -- private part is the full declaration.
+ -- Swap the two entities. Now Private is the full type entity and Full
+ -- is the private one. They will be swapped back at the end of the
+ -- private part. This swapping ensures that the entity that is visible
+ -- in the private part is the full declaration.
Exchange_Entities (Priv, Full);
Append_Entity (Full, Scope (Full));
if Ekind (Typ) = E_Record_Type_With_Private then
- -- Handle the following erronous case:
+ -- Handle the following erroneous case:
-- type Private_Type is tagged private;
-- private
-- type Private_Type is new Type_Implementing_Iface;
-- but it means we don't have to struggle to meet the requirements in
-- the RM for having Preelaborable Initialization. Otherwise we
-- require that the type meets the RM rules. But we can't check that
- -- yet, because of the rule about overriding Ininitialize, so we
- -- simply set a flag that will be checked at freeze time.
+ -- yet, because of the rule about overriding Initialize, so we simply
+ -- set a flag that will be checked at freeze time.
if not In_Predefined_Unit (Full_T) then
Set_Must_Have_Preelab_Init (Full_T);
exit;
end if;
- -- The other case is appearence in a subprogram body. This may
+ -- The other case is appearance in a subprogram body. This may
-- be a violation if this is a library level subprogram, and it
-- turns out to be used as the main program, but only the
-- binder knows that, so just record the occurrence.
Get_First_Interp (FirstX, I, It);
while Present (It.Nam) loop
- -- For each intepretation of the first expression, we only
- -- add the intepretation if every other expression in the
+ -- For each interpretation of the first expression, we only
+ -- add the interpretation if every other expression in the
-- case expression alternatives has a compatible type.
Alt := Next (First (Alternatives (N)));
Get_First_Interp (Then_Expr, I, It);
while Present (It.Nam) loop
- -- For each possible intepretation of the Then Expression,
+ -- For each possible interpretation of the Then Expression,
-- add it only if the else expression has a compatible type.
-- Is this right if Else_Expr is empty?
-- Finally, the formal and the actual may be private extensions,
-- but the generic is declared in a child unit of the parent, and
- -- an addtional step is needed to retrieve the proper scope.
+ -- an additional step is needed to retrieve the proper scope.
elsif In_Instance
and then Present (Parent_Subtype (Etype (Base_Type (Prefix_Type))))
null;
else
- -- Save candidate type for subsquent error message, if any
+ -- Save candidate type for subsequent error message, if any
if not Is_Limited_Type (T1) then
Candidate_Type := T1;
-- (Ada 2012: AI05-0125-1): If S is a dispatching operation then
-- it may have overridden some hidden inherited primitive. Update
- -- Overriden_Subp to avoid spurious errors when checking the
+ -- Overridden_Subp to avoid spurious errors when checking the
-- overriding indicator.
if Ada_Version >= Ada_2012
end;
end if;
- -- Now we can copy the tree, doing any required substituations
+ -- Now we can copy the tree, doing any required substitutions
CP := New_Copy_Tree (Prag, Map => Map, New_Scope => Current_Scope);
procedure New_Private_Type (N : Node_Id; Id : Entity_Id; Def : Node_Id) is
begin
- -- For other than Ada 2012, enter tha name in the current scope
+ -- For other than Ada 2012, enter the name in the current scope
if Ada_Version < Ada_2012 then
Enter_Name (Id);
function May_Be_Used_Primitive_Of (T : Entity_Id) return Boolean;
-- An operator may be primitive in several types, if they are declared
- -- in the same scope as the operator. To determine the use-visiblity of
+ -- in the same scope as the operator. To determine the use-visibility of
-- the operator in such cases we must examine all types in the profile.
------------------------------
end if;
-- Indicate that this is an overriding operation,
- -- and replace the overriden entry in the list of
+ -- and replace the overridden entry in the list of
-- primitive operations, which is used for xref
-- generation subsequently.
-- The location of entities that come from source in the list of
-- primitives of the tagged type must follow their order of occurrence
- -- in the sources to fulfill the C++ ABI. If the overriden entity is a
+ -- in the sources to fulfill the C++ ABI. If the overridden entity is a
-- primitive of an interface that is not an ancestor of this tagged
-- type (that is, it is an entity added to the list of primitives by
-- Derive_Interface_Progenitors), then we must append the new entity
Remove_Elmt (Primitive_Operations (Tagged_Type), Elmt);
Append_Elmt (New_Op, Primitive_Operations (Tagged_Type));
- -- The new primitive replaces the overriden entity. Required to ensure
+ -- The new primitive replaces the overridden entity. Required to ensure
-- that overriding primitive is assigned the same dispatch table slot.
else
-- in the list of primitives of Tagged_Type. This latter search is needed
-- when the interface primitive is covered by a private subprogram. If the
-- primitive has not been covered yet then return the entity that will be
- -- overriden when the primitive is covered (that is, return the entity
+ -- overridden when the primitive is covered (that is, return the entity
-- whose alias attribute references the interface primitive). If none of
-- these entities is found then return Empty.
--
-- If Stat is set True on return, then Is_Static_Expression is also set
-- true in node N. There are some cases where this is over-enthusiastic,
- -- e.g. in the two operand case below, for string comaprison, the result
+ -- e.g. in the two operand case below, for string comparison, the result
-- is not static even though the two operands are static. In such cases,
-- the caller must reset the Is_Static_Expression flag in N.
elsif Is_Array_Type (T1) then
-- If either subtype is unconstrained then both must be, and if both
- -- are unconstrained then no further checking is neede.
+ -- are unconstrained then no further checking is needed.
if not Is_Constrained (T1) or else not Is_Constrained (T2) then
return not (Is_Constrained (T1) or else Is_Constrained (T2));
-- For unchecked deallocation, error to deallocate from empty pool.
-- Note: this test used to be in Exp_Intr as a warning, but AI 157
- -- issues a binding intepretation that this should be an error, and
+ -- issues a binding interpretation that this should be an error, and
-- consequently it needs to be done in the semantic analysis so that
-- the error is issued even in semantics only mode.
end;
end if;
- -- Note: we do not analye the pragma at this point. Instead we
+ -- Note: we do not analyze the pragma at this point. Instead we
-- delay this analysis until the end of the declarative part in
-- which the pragma appears. This implements the required delay
-- in this analysis, allowing forward references. The analysis
-- whether a given pragma is significant.
-- -1 indicates that references in any argument position are significant
- -- 0 indicates that appearence in any argument is not significant
- -- +n indicates that appearence as argument n is significant, but all
+ -- 0 indicates that appearance in any argument is not significant
+ -- +n indicates that appearance as argument n is significant, but all
-- other arguments are not significant
-- 99 special processing required (e.g. for pragma Check)
-- expander does, so we match its logic here).
-- The second case is mod where either operand can be negative.
- -- In this case, the back end has to generate additonal tests.
+ -- In this case, the back end has to generate additional tests.
if (Nkind (N) = N_Op_Rem and then (LNeg and RNeg))
or else
then
null;
- -- Any other use is an eror
+ -- Any other use is an error
else
Error_Msg_N
-- Note: When the SCIL node is generated the private and full-view
-- of the tagged types may have been swapped and hence the node
-- referenced by attribute SCIL_Entity may be the private view.
- -- Therefore, in order to uniformily locate the full-view we use
+ -- Therefore, in order to uniformly locate the full-view we use
-- attribute Underlying_Type.
pragma Assert
-- safely used by New_Copy_Tree, since there is no case of a recursive
-- call from the processing inside New_Copy_Tree.
- NCT_Hash_Threshhold : constant := 20;
+ NCT_Hash_Threshold : constant := 20;
-- If there are more than this number of pairs of entries in the
-- map, then Hash_Tables_Used will be set, and the hash tables will
-- be initialized and used for the searches.
-- Set to True if hash tables are in use
NCT_Table_Entries : Nat;
- -- Count entries in table to see if threshhold is reached
+ -- Count entries in table to see if threshold is reached
NCT_Hash_Table_Setup : Boolean := False;
-- Set to True if hash table contains data. We set this True if we
-- Itype references within the copied tree.
-- The following hash tables are used if the Map supplied has more
- -- than hash threshhold entries to speed up access to the map. If
+ -- than hash threshold entries to speed up access to the map. If
-- there are fewer entries, then the map is searched sequentially
-- (because setting up a hash table for only a few entries takes
-- more time than it saves.
else
NCT_Table_Entries := NCT_Table_Entries + 1;
- if NCT_Table_Entries > NCT_Hash_Threshhold then
+ if NCT_Table_Entries > NCT_Hash_Threshold then
Build_NCT_Hash_Tables;
end if;
end if;
Next_Elmt (Elmt);
end loop;
- if NCT_Table_Entries > NCT_Hash_Threshhold then
+ if NCT_Table_Entries > NCT_Hash_Threshold then
Build_NCT_Hash_Tables;
else
NCT_Hash_Tables_Used := False;
then
return Original_Corresponding_Operation (Alias (S));
- -- If S overrides an inherted subprogram S2 the original corresponding
+ -- If S overrides an inherited subprogram S2 the original corresponding
-- operation of S is the original corresponding operation of S2
elsif Present (Overridden_Operation (S)) then
-- initialized (in particular in the record case, that at least one
-- component has an initialization expression). Note that initialization
-- resulting from the use of pragma Normalized_Scalars does not count.
- -- Include_Implicit controls whether implicit initialiation of access
+ -- Include_Implicit controls whether implicit initialization of access
-- values to null, and of discriminant values, is counted as making the
-- type be partially initialized. For the default setting of True, these
-- implicit cases do count, and discriminated types or types containing
-- access values not explicitly initialized will return True. Otherwise
-- if Include_Implicit is False, these cases do not count as making the
- -- type be partially initialied.
+ -- type be partially initialized.
function Is_Potentially_Persistent_Type (T : Entity_Id) return Boolean;
-- Determines if type T is a potentially persistent type. A potentially
-- or a pragma, and a warning is worthwhile as well.
function Check_System_Aux return Boolean;
- -- Before giving a warning on a with_clause for System, check wheter
+ -- Before giving a warning on a with_clause for System, check whether
-- a system extension is present.
function Find_Package_Renaming
-- variable in question, or if the entity in question
-- is an OUT or IN OUT parameter, which which case
-- the caller can reference it after the exception
- -- hanlder completes
+ -- handler completes.
else
if Is_Formal (Ent) then
Warn_On_Overridden_Size : Boolean := False;
-- Warn when explicit record component clause or array component_size
- -- clause specifies a size that overrides a size for the typen which was
+ -- clause specifies a size that overrides a size for the type which was
-- set with an explicit size clause. Off by default, set by -gnatw.s (but
-- not -gnatwa).
-- Has_Pragma_Suppress_All (Flag14-Sem)
-- This flag is set in an N_Compilation_Unit node if the Suppress_All
- -- pragma appears anywhere in the unit. This accomodates the rather
+ -- pragma appears anywhere in the unit. This accommodates the rather
-- strange placement rules of other compilers (DEC permits it at the
-- end of a unit, and Rational allows it as a program unit pragma). We
-- allow it anywhere at all, and consider it equivalent to a pragma
-- Next_Exit_Statement (Node3-Sem)
-- Present in N_Exit_Statement nodes. The exit statements for a loop are
- -- chained (in reverse order of appearence) from the First_Exit_Statement
+ -- chained (in reverse order of appearance) from the First_Exit_Statement
-- field of the E_Loop entity for the loop. Next_Exit_Statement points to
-- the next entry on this chain (Empty = end of list).
-- A postorder traversal of the tree whose nodes are units and whose
-- links are with_clauses defines the order in which Inspector must
-- examine a compiled unit and its full context. This ordering ensures
- -- that any subprogram call is examined after the subprogram declartion
+ -- that any subprogram call is examined after the subprogram declaration
-- has been seen.
-- Next_Named_Actual (Node4-Sem)
-- secondary stack.
-- Suppress_Assignment_Checks (Flag18-Sem)
- -- Used in genererated N_Assignment_Statement nodes to suppress predicate
+ -- Used in generated N_Assignment_Statement nodes to suppress predicate
-- and range checks in cases where the generated code knows that the
- -- value being assigned is in range and satisifies any predicate. Also
+ -- value being assigned is in range and satisfies any predicate. Also
-- can be set in N_Object_Declaration nodes, to similarly suppress any
-- checks on the initializing value.
-- Suppress_Assignment_Checks (Flag18-Sem)
-- Note: if a range check is required, then the Do_Range_Check flag
- -- is set in the Expression (right hand side), with the check b6ing
+ -- is set in the Expression (right hand side), with the check being
-- done against the type of the Name (left hand side).
-- Note: the back end places some restrictions on the form of the
-- explicit loop identifier. Otherwise the parser leaves this field
-- set to Empty, and then the semantic processing for a loop statement
-- creates an identifier, setting the Has_Created_Identifier flag to
- -- True. So after semantic anlaysis, the Identifier is always set,
+ -- True. So after semantic analysis, the Identifier is always set,
-- referencing an identifier whose entity has an Ekind of E_Loop.
--------------------------
-- CASE_EXPRESSION_ALTERNATIVE
-- {CASE_EXPRESSION_ALTERNATIVE}
- -- Note that the Alternatives cannot include pragmas (this constrasts
+ -- Note that the Alternatives cannot include pragmas (this contrasts
-- with the situation of case statements where pragmas are allowed).
-- N_Case_Expression
-- Note: The Actions field temporarily holds any actions associated with
-- evaluation of the Expression. During expansion of the case expression
- -- these actions are wrapped into the an N_Expressions_With_Actions node
+ -- these actions are wrapped into an N_Expressions_With_Actions node
-- replacing the original expression.
----------------------------
-- And we add the additional constructs
- -- PRIMARY ::= ( CONDITIONAL_EXPRESION )
+ -- PRIMARY ::= ( CONDITIONAL_EXPRESSION )
-- PRAGMA_ARGUMENT_ASSOCIATION ::= CONDITIONAL_EXPRESSION
-- Note: if we have (IF x1 THEN x2 ELSIF x3 THEN x4 ELSE x5) then it
/*
* For VMS, gsocket.h can't include sockets-related DEC C header files
* when building the runtime (because these files are in a DEC C text library
- * (DECC$RTLDEF.TLB) not accessable to GCC). So, we generate a separate header
+ * (DECC$RTLDEF.TLB) not accessible to GCC). So, we generate a separate header
* file along with s-oscons.ads and include it here.
*/
# include "s-oscons.h"
end if;
end OK_Boolean_Operand;
- -- Start of processig for Check_Boolean_Operator
+ -- Start of processing for Check_Boolean_Operator
begin
if Style_Check_Boolean_And_Or
function Is_Internal_GCC_Switch (Switch_Chars : String) return Boolean;
-- Returns True iff Switch_Chars represents an internal GCC switch to be
-- followed by a single argument, such as -dumpbase, --param or -auxbase.
- -- Eventhough passed by the "gcc" driver, these need not be stored in ALI
+ -- Even though passed by the "gcc" driver, these need not be stored in ALI
-- files and may safely be ignored by non GCC back-ends.
function Switch_Last (Switch_Chars : String) return Natural;
-- Returns True if an integer is at the current scan location or an equal
-- sign. This is used as a guard for calling Scan_Nat. Switch_Chars is the
-- string containing the switch, and Ptr points just past the switch
- -- character. Max is the maximum alllowed value of Ptr.
+ -- character. Max is the maximum allowed value of Ptr.
procedure Scan_Nat
(Switch_Chars : String;
-- Scan natural integer parameter for switch. On entry, Ptr points just
-- past the switch character, on exit it points past the last digit of the
-- integer value. Max is the maximum allowed value of Ptr, so the scan is
- -- restricted to Switch_Chars (Ptr .. Max). It is posssible for Ptr to be
+ -- restricted to Switch_Chars (Ptr .. Max). It is possible for Ptr to be
-- one greater than Max on return if the entire string is digits. Scan_Nat
-- will skip an optional equal sign if it is present. Nat_Present must be
-- True, or an error will be signalled.
#else
-/* VMS does not need __gnat_locatime_tzoff */
+/* VMS does not need __gnat_localtime_tzoff */
#if defined (VMS)
-/* Other targets except Lynx, VMS and Windows provide a standard locatime_r */
+/* Other targets except Lynx, VMS and Windows provide a standard localtime_r */
#else
So we recognize only a few registers (t7, t9, ra) within
the procedure prologue as valid return address registers.
If we encounter a return instruction, we extract the
- the return address register from it.
+ return address register from it.
FIXME: Rewriting GDB to access the procedure descriptors,
e.g. via the minimal symbol table, might obviate this hack. */
-- is not available in older base compilers.
-- We need to deal with integer values that can be signed or unsigned, so
- -- we need to accomodate the maximum range of both cases.
+ -- we need to accommodate the maximum range of both cases.
type Int_Value_Type is record
Positive : Boolean;