a-textio.ads, [...]: Fix comment typos.

gcc/ada/
	* a-textio.ads, a-witeio.ads, a-ztexio.ads, ali.ads,
	einfo.ads, erroutc.adb, erroutc.ads, exp_attr.adb,
	exp_imgv.adb, exp_intr.adb, exp_pakd.adb,
	exp_pakd.ads, exp_prag.adb, exp_smem.adb,
	exp_tss.ads, exp_util.adb, exp_util.ads,
	exp_vfpt.adb, freeze.adb, freeze.ads,
	frontend.adb, g-alleve.adb, g-altcon.adb,
	g-altive.ads, g-alveop.ads, g-alvevi.ads,
	g-arrspl.adb, g-busorg.ads, g-calend.adb,
	g-calend.ads, g-casuti.ads, g-cgideb.adb,
	g-comlin.adb, g-comlin.ads, g-curexc.ads,
	g-debpoo.adb, g-debpoo.ads, g-decstr.adb,
	g-dirope.adb, g-dirope.ads, g-dynhta.ads,
	g-dyntab.adb, g-encstr.ads, g-excact.ads,
	g-except.ads, g-expect.ads, g-heasor.adb,
	g-hesora.adb, g-hesorg.adb, g-htable.ads,
	g-locfil.ads, g-md5.adb, g-md5.ads,
	g-memdum.ads, g-moreex.ads, g-os_lib.adb,
	g-pehage.adb, g-pehage.ads, g-regexp.adb,
	g-regexp.ads, g-regpat.adb, g-regpat.ads,
	g-soccon-aix.ads, g-soccon-darwin.ads,
	g-soccon-freebsd.ads, g-soccon-hpux-ia64.ads,
	g-soccon-hpux.ads, g-soccon-irix.ads,
	g-soccon-linux-64.ads, g-soccon-linux-ppc.ads,
	g-soccon-linux-x86.ads, g-soccon-lynxos.ads,
	g-soccon-mingw.ads, g-soccon-solaris-64.ads,
	g-soccon-solaris.ads, g-soccon-tru64.ads,
	g-soccon-vms.ads, g-soccon-vxworks.ads,
	g-soccon.ads, g-socket.adb, g-socket.ads,
	g-socthi-mingw.adb, g-socthi-vms.adb,
	g-socthi-vxworks.adb, g-soliop-mingw.ads,
	g-soliop-solaris.ads, g-soliop.ads, g-spipat.adb,
	g-spipat.ads, g-string.adb, g-stsifd-sockets.adb: Fix comment
	typos.

From-SVN: r133735
This commit is contained in:
Ralf Wildenhues 2008-03-30 19:39:01 +00:00 committed by Ralf Wildenhues
parent 8ae6e4a4dd
commit e14c931f31
92 changed files with 250 additions and 213 deletions

View File

@ -1,3 +1,40 @@
2008-03-30 Ralf Wildenhues <Ralf.Wildenhues@gmx.de>
* a-textio.ads, a-witeio.ads, a-ztexio.ads, ali.ads,
einfo.ads, erroutc.adb, erroutc.ads, exp_attr.adb,
exp_imgv.adb, exp_intr.adb, exp_pakd.adb,
exp_pakd.ads, exp_prag.adb, exp_smem.adb,
exp_tss.ads, exp_util.adb, exp_util.ads,
exp_vfpt.adb, freeze.adb, freeze.ads,
frontend.adb, g-alleve.adb, g-altcon.adb,
g-altive.ads, g-alveop.ads, g-alvevi.ads,
g-arrspl.adb, g-busorg.ads, g-calend.adb,
g-calend.ads, g-casuti.ads, g-cgideb.adb,
g-comlin.adb, g-comlin.ads, g-curexc.ads,
g-debpoo.adb, g-debpoo.ads, g-decstr.adb,
g-dirope.adb, g-dirope.ads, g-dynhta.ads,
g-dyntab.adb, g-encstr.ads, g-excact.ads,
g-except.ads, g-expect.ads, g-heasor.adb,
g-hesora.adb, g-hesorg.adb, g-htable.ads,
g-locfil.ads, g-md5.adb, g-md5.ads,
g-memdum.ads, g-moreex.ads, g-os_lib.adb,
g-pehage.adb, g-pehage.ads, g-regexp.adb,
g-regexp.ads, g-regpat.adb, g-regpat.ads,
g-soccon-aix.ads, g-soccon-darwin.ads,
g-soccon-freebsd.ads, g-soccon-hpux-ia64.ads,
g-soccon-hpux.ads, g-soccon-irix.ads,
g-soccon-linux-64.ads, g-soccon-linux-ppc.ads,
g-soccon-linux-x86.ads, g-soccon-lynxos.ads,
g-soccon-mingw.ads, g-soccon-solaris-64.ads,
g-soccon-solaris.ads, g-soccon-tru64.ads,
g-soccon-vms.ads, g-soccon-vxworks.ads,
g-soccon.ads, g-socket.adb, g-socket.ads,
g-socthi-mingw.adb, g-socthi-vms.adb,
g-socthi-vxworks.adb, g-soliop-mingw.ads,
g-soliop-solaris.ads, g-soliop.ads, g-spipat.adb,
g-spipat.ads, g-string.adb, g-stsifd-sockets.adb: Fix comment
typos.
2008-03-27 Eric Botcazou <ebotcazou@adacore.com>
* decl.c (gnat_to_gnu_entity) <E_Procedure>: Also set the public flag

View File

@ -317,7 +317,7 @@ private
-- omitted on output unless an explicit New_Page call is made before
-- closing the file. No page mark is added when a file is appended to,
-- so, in accordance with the permission in (RM A.10.2(4)), there may
-- or may not be a page mark separating preexising text in the file
-- or may not be a page mark separating preexisting text in the file
-- from the new text to be written.
-- A file mark is marked by the physical end of file. In DOS translation
@ -354,7 +354,7 @@ private
Self : aliased File_Type;
-- Set to point to the containing Text_AFCB block. This is used to
-- implement the Current_{Error,Input,Ouput} functions which return
-- implement the Current_{Error,Input,Output} functions which return
-- a File_Access, the file access value returned is a pointer to
-- the Self field of the corresponding file.

View File

@ -138,7 +138,7 @@ package Ada.Wide_Text_IO is
-- Buffer control --
--------------------
-- Note: The paramter file is in out in the RM, but as pointed out
-- Note: The parameter file is in out in the RM, but as pointed out
-- in <<95-5166.a Tucker Taft 95-6-23>> this is clearly an oversight.
procedure Flush (File : File_Type);
@ -319,7 +319,7 @@ private
-- omitted on output unless an explicit New_Page call is made before
-- closing the file. No page mark is added when a file is appended to,
-- so, in accordance with the permission in (RM A.10.2(4)), there may
-- or may not be a page mark separating preexising text in the file
-- or may not be a page mark separating preexisting text in the file
-- from the new text to be written.
-- A file mark is marked by the physical end of file. In DOS translation
@ -352,12 +352,12 @@ private
Self : aliased File_Type;
-- Set to point to the containing Text_AFCB block. This is used to
-- implement the Current_{Error,Input,Ouput} functions which return
-- implement the Current_{Error,Input,Output} functions which return
-- a File_Access, the file access value returned is a pointer to
-- the Self field of the corresponding file.
Before_LM : Boolean := False;
-- This flag is used to deal with the anomolies introduced by the
-- This flag is used to deal with the anomalies introduced by the
-- peculiar definition of End_Of_File and End_Of_Page in Ada. These
-- functions require looking ahead more than one character. Since
-- there is no convenient way of backing up more than one character,

View File

@ -138,7 +138,7 @@ package Ada.Wide_Wide_Text_IO is
-- Buffer control --
--------------------
-- Note: The paramter file is in out in the RM, but as pointed out
-- Note: The parameter file is in out in the RM, but as pointed out
-- in <<95-5166.a Tucker Taft 95-6-23>> this is clearly an oversight.
procedure Flush (File : File_Type);
@ -319,7 +319,7 @@ private
-- omitted on output unless an explicit New_Page call is made before
-- closing the file. No page mark is added when a file is appended to,
-- so, in accordance with the permission in (RM A.10.2(4)), there may
-- or may not be a page mark separating preexising text in the file
-- or may not be a page mark separating preexisting text in the file
-- from the new text to be written.
-- A file mark is marked by the physical end of file. In DOS translation
@ -352,12 +352,12 @@ private
Self : aliased File_Type;
-- Set to point to the containing Text_AFCB block. This is used to
-- implement the Current_{Error,Input,Ouput} functions which return
-- implement the Current_{Error,Input,Output} functions which return
-- a File_Access, the file access value returned is a pointer to
-- the Self field of the corresponding file.
Before_LM : Boolean := False;
-- This flag is used to deal with the anomolies introduced by the
-- This flag is used to deal with the anomalies introduced by the
-- peculiar definition of End_Of_File and End_Of_Page in Ada. These
-- functions require looking ahead more than one character. Since
-- there is no convenient way of backing up more than one character,

View File

@ -845,12 +845,12 @@ package ALI is
Oref_File_Num : Sdep_Id;
-- This field is set to No_Sdep_Id if the entity doesn't override any
-- other entity, or to the dependency reference for the overriden
-- other entity, or to the dependency reference for the overridden
-- entity.
Oref_Line : Nat;
Oref_Col : Nat;
-- These two fields are set to the line and column of the overriden
-- These two fields are set to the line and column of the overridden
-- entity.
First_Xref : Nat;

View File

@ -2620,7 +2620,7 @@ package Einfo is
-- which does not also have this flag set to True. For a variable or
-- or constant, if the flag is set, then the type of the object must
-- either be declared at the library level, or it must also have the
-- flag set (since to allocate the oject statically, its type must
-- flag set (since to allocate the object statically, its type must
-- also be elaborated globally).
-- Is_Static_Dispatch_Table_Entity (Flag234)
@ -2732,7 +2732,7 @@ package Einfo is
-- package. Indicates that the entity must be made visible in the body
-- of the instance, to reproduce the visibility of the generic. This
-- simplifies visibility settings in instance bodies.
-- ??? confusion in abovecomments between being present and being set
-- ??? confusion in above comments between being present and being set
-- Is_VMS_Exception (Flag133)
-- Present in all entities. Set only for exception entities where the
@ -2766,13 +2766,13 @@ package Einfo is
-- Kill_Elaboration_Checks (Flag32)
-- Present in all entities. Set by the expander to kill elaboration
-- checks which are known not to be needed. Equivalent in effect to
-- the use of pragma Supress (Elaboration_Checks) for that entity
-- the use of pragma Suppress (Elaboration_Checks) for that entity
-- except that the effect is permanent and cannot be undone by a
-- subsequent pragma Unsuppress.
-- Kill_Range_Checks (Flag33)
-- Present in all entities. Equivalent in effect to the use of pragma
-- Supress (Range_Checks) for that entity except that the result is
-- Suppress (Range_Checks) for that entity except that the result is
-- permanent and cannot be undone by a subsequent pragma Unsuppress.
-- This is currently only used in one odd situation in Sem_Ch3 for
-- record types, and it would be good to get rid of it???
@ -2780,7 +2780,7 @@ package Einfo is
-- Kill_Tag_Checks (Flag34)
-- Present in all entities. Set by the expander to kill elaboration
-- checks which are known not to be needed. Equivalent in effect to
-- the use of pragma Supress (Tag_Checks) for that entity except
-- the use of pragma Suppress (Tag_Checks) for that entity except
-- that the result is permanent and cannot be undone by a subsequent
-- pragma Unsuppress.
@ -2805,7 +2805,7 @@ package Einfo is
-- associated entities is attached (blocks, class subtypes and types,
-- entries, functions, loops, packages, procedures, protected objects,
-- record types and subtypes, private types, task types and subtypes).
-- Points to a the last entry in the list of associated entities chained
-- Points to the last entry in the list of associated entities chained
-- through the Next_Entity field. Empty if no entities are chained.
-- Limited_View (Node23)
@ -2819,7 +2819,7 @@ package Einfo is
-- Present in enumeration types and subtypes. Non-empty only for the
-- case of an enumeration root type, where it contains the entity for
-- the generated indexes entity. See unit Exp_Imgv for full details of
-- the nature and use of this entity for implkementing the Image and
-- the nature and use of this entity for implementing the Image and
-- Value attributes for the enumeration type in question.
--
-- Lit_Strings (Node16)
@ -3169,7 +3169,7 @@ package Einfo is
-- Parameter_Mode (synthesized)
-- Applies to formal parameter entities. This is a synonym for Ekind,
-- used when obtaining the formal kind of a formal parameter (the result
-- is one of E_[In/Out/In_Out]_Paramter)
-- is one of E_[In/Out/In_Out]_Parameter)
-- Parent_Subtype (Node19)
-- Present in E_Record_Type. Points to the subtype to use for a
@ -3254,9 +3254,9 @@ package Einfo is
-- Referenced (Flag156)
-- Present in all entities. Set if the entity is referenced, except for
-- the case of an appearence of a simple variable that is not a renaming
-- the case of an appearance of a simple variable that is not a renaming
-- as the left side of an assignment in which case Referenced_As_LHS is
-- set instead, or a similar appearence as an out parameter actual, in
-- set instead, or a similar appearance as an out parameter actual, in
-- which case As_Out_Parameter_Parameter is set.
-- Referenced_As_LHS (Flag36):
@ -3307,7 +3307,7 @@ package Einfo is
-- Renamed_Entity (Node18)
-- Present in exceptions, packages, subprograms and generic units. Set
-- for entities that are defined by a renaming declaration. Denotes the
-- renamed entity, or transititively the ultimate renamed entity if
-- renamed entity, or transitively the ultimate renamed entity if
-- there is a chain of renaming declarations. Empty if no renaming.
-- Renamed_In_Spec (Flag231)
@ -3367,11 +3367,11 @@ package Einfo is
-- Reverse_Bit_Order (Flag164) [base type only]
-- Present in all record type entities. Set if a valid pragma an
-- attribute represention clause for Bit_Order has reversed the order of
-- bits from the default value. When this flag is set, a component clause
-- must specify a set of bits entirely contained in a single storage unit
-- (Ada 95) or a single machine scalar (see Ada 2005 AI-133), or must
-- occupy in integral number of storage units.
-- attribute representation clause for Bit_Order has reversed the order
-- of bits from the default value. When this flag is set, a component
-- clause must specify a set of bits entirely contained in a single
-- storage unit (Ada 95) or a single machine scalar (see Ada 2005
-- AI-133), or must occupy in integral number of storage units.
-- RM_Size (Uint13)
-- Present in all type and subtype entities. Contains the value of
@ -3387,7 +3387,7 @@ package Einfo is
-- type of the class covered by the CW type, otherwise returns the
-- ultimate derivation ancestor of the given type. This function
-- preserves the view, i.e. the Root_Type of a partial view is the
-- partial view of the ulimate ancestor, the Root_Type of a full view
-- partial view of the ultimate ancestor, the Root_Type of a full view
-- is the full view of the ultimate ancestor. Note that this function
-- does not correspond exactly to the use of root type in the RM, since
-- in the RM root type applies to a class of types, not to a type.
@ -4495,7 +4495,7 @@ package Einfo is
-- For each enumeration value defined in Entity_Kind we list all the
-- attributes defined in Einfo which can legally be applied to an entity
-- of that kind. The implementation of the attribute functions (and for
-- non-synthetized attributes, of the corresponding set procedures) are
-- non-synthesized attributes, of the corresponding set procedures) are
-- in the Einfo body.
-- The following attributes apply to all entities
@ -5497,7 +5497,7 @@ package Einfo is
-- There are four types of alignment possible for array and record
-- types, and a field in the type entities contains a value of the
-- following type indicating which alignment choice applies. For full
-- details of the meaning of these aligment types, see description
-- details of the meaning of these alignment types, see description
-- of the Component_Alignment pragma
type Component_Alignment_Kind is (

View File

@ -176,7 +176,7 @@ package body Erroutc is
Delete_Msg (M1, M2);
return;
-- If M2 continuatins have run out, we delete M2
-- If M2 continuations have run out, we delete M2
elsif N2 = No_Error_Msg or else not Errors.Table (N2).Msg_Cont then
Delete_Msg (M2, M1);
@ -968,7 +968,7 @@ package body Erroutc is
Set_Msg_Char (UI_Image_Buffer (J));
end loop;
-- The following assignment ensures that a second carret insertion
-- The following assignment ensures that a second caret insertion
-- character will correspond to the Error_Msg_Uint_2 parameter. We
-- suppress possible validity checks in case operating in -gnatVa mode,
-- and Error_Msg_Uint_2 is not needed and has not been set.

View File

@ -36,7 +36,7 @@ package Erroutc is
-- type, and is used by Add_Class to insert 'Class at the proper point
Continuation : Boolean := False;
-- Indicates if current message is a continuation. Intialized from the
-- Indicates if current message is a continuation. Initialized from the
-- Msg_Cont parameter in Error_Msg_Internal and then set True if a \
-- insertion character is encountered.
@ -81,9 +81,9 @@ package Erroutc is
Max_Msg_Length : constant := 1024 + 2 * Int (Column_Number'Last);
-- Maximum length of error message. The addition of 2 * Column_Number'Last
-- ensures that two insertion tokens of maximum length can be accomodated.
-- ensures that two insertion tokens of maximum length can be accommodated.
-- The value of 1024 is an arbitrary value that should be more than long
-- enough to accomodate any reasonable message (and for that matter, some
-- enough to accommodate any reasonable message (and for that matter, some
-- pretty unreasonable messages!)
Msg_Buffer : String (1 .. Max_Msg_Length);
@ -115,7 +115,7 @@ package Erroutc is
No_Error_Msg : constant Error_Msg_Id := 0;
-- A constant which is different from any value returned by Get_Error_Id.
-- Typically used by a client to indicate absense of a saved Id value.
-- Typically used by a client to indicate absence of a saved Id value.
Cur_Msg : Error_Msg_Id := No_Error_Msg;
-- Id of most recently posted error message
@ -235,7 +235,7 @@ package Erroutc is
-- end of the current source file. A subsequent pragma Warnings (On)
-- adjusts the end point of this entry appropriately.
-- If all warnings are suppressed by comamnd switch, then there is a
-- If all warnings are suppressed by command switch, then there is a
-- dummy entry (put there by Errout.Initialize) at the start of the
-- table which covers all possible Source_Ptr values. Note that the
-- source pointer values in this table always reference the original

View File

@ -624,7 +624,7 @@ package body Exp_Attr is
-- is done only for "Address!(Prim'Unrestricted_Access)" nodes.
-- At this stage other cases in which the designated type is
-- still a subprogram (instead of an E_Subprogram_Type) are
-- wrong because the semantics must have overriden the type of
-- wrong because the semantics must have overridden the type of
-- the node with the type imposed by the context.
pragma Assert (Nkind (Parent (N)) = N_Unchecked_Type_Conversion

View File

@ -556,7 +556,7 @@ package body Exp_Imgv is
-- Enum'Val (Value_Enumeration_NN (typS, typI'Address, Num, X))
-- where typS and typI and the Lit_Strings and Lit_Indexes entities
-- from T's root type entitym and Num is Enum'Pos (Enum'Last). The
-- from T's root type entity, and Num is Enum'Pos (Enum'Last). The
-- Value_Enumeration_NN function will search the tables looking for
-- X and return the position number in the table if found which is
-- used to provide the result of 'Value (using Enum'Val). If the

View File

@ -87,7 +87,7 @@ package body Exp_Intr is
-- K is the kind for the shift node
procedure Expand_Unc_Conversion (N : Node_Id; E : Entity_Id);
-- Expand a call to an instantiation of Unchecked_Convertion into a node
-- Expand a call to an instantiation of Unchecked_Conversion into a node
-- N_Unchecked_Type_Conversion.
procedure Expand_Unc_Deallocation (N : Node_Id);
@ -97,7 +97,7 @@ package body Exp_Intr is
procedure Expand_To_Address (N : Node_Id);
procedure Expand_To_Pointer (N : Node_Id);
-- Expand a call to corresponding function, declared in an instance of
-- System.Addess_To_Access_Conversions.
-- System.Address_To_Access_Conversions.
procedure Expand_Source_Info (N : Node_Id; Nam : Name_Id);
-- Rewrite the node by the appropriate string or positive constant.

View File

@ -535,7 +535,7 @@ package body Exp_Pakd is
-- directly using Insert_Action.
------------------------------
-- Compute_Linear_Subcsript --
-- Compute_Linear_Subscript --
------------------------------
procedure Compute_Linear_Subscript
@ -2010,7 +2010,7 @@ package body Exp_Pakd is
Left_Opnd => Make_Shift_Right (Obj, Shift),
Right_Opnd => Lit);
-- We neded to analyze this before we do the unchecked convert
-- We needed to analyze this before we do the unchecked convert
-- below, but we need it temporarily attached to the tree for
-- this analysis (hence the temporary Set_Parent call).

View File

@ -218,7 +218,7 @@ package Exp_Pakd is
-- Note: although this routine is included in the expander package for
-- packed types, it is actually called unconditionally from Freeze,
-- whether or not expansion (and code generation) is enabled. We do this
-- since we want gigi to be able to properly compute type charactersitics
-- since we want gigi to be able to properly compute type characteristics
-- (for the Data Decomposition Annex of ASIS, and possible other future
-- uses) even if code generation is not active. Strictly this means that
-- this procedure is not part of the expander, but it seems appropriate
@ -263,7 +263,7 @@ package Exp_Pakd is
function Involves_Packed_Array_Reference (N : Node_Id) return Boolean;
-- N is the node for a name. This function returns true if the name
-- involves a packed array reference. A node involves a packed array
-- reference if it is itself an indexed compoment referring to a bit-
-- reference if it is itself an indexed component referring to a bit-
-- packed array, or it is a selected component whose prefix involves
-- a packed array reference.

View File

@ -330,7 +330,7 @@ package body Exp_Prag is
and then Is_RTE (Entity (Name (N)), RE_Raise_Assert_Failure)
then
-- If original condition was a Standard.False, we assume that this is
-- indeed intented to raise assert error and no warning is required.
-- indeed intended to raise assert error and no warning is required.
if Is_Entity_Name (Original_Node (Cond))
and then Entity (Original_Node (Cond)) = Standard_False

View File

@ -52,7 +52,7 @@ package body Exp_Smem is
procedure Add_Write_After (N : Node_Id);
-- Insert a Shared_Var_WOpen call for variable after the node
-- Insert_Node, as recorded by On_Lhs_Of_Assigment (where it points
-- Insert_Node, as recorded by On_Lhs_Of_Assignment (where it points
-- to the assignment statement) or Is_Out_Actual (where it points to
-- the procedure call statement).

View File

@ -50,9 +50,9 @@ package Exp_Tss is
-------------------------
-- In the current version of this package, only the case of generating a
-- TSS at the point of declaration of the type is accomodated. A clear
-- TSS at the point of declaration of the type is accommodated. A clear
-- improvement would be to follow through with the full implementation
-- as described above, and also accomodate the requirement of generating
-- as described above, and also accommodate the requirement of generating
-- only one copy in a given object file.
-- For now, we deal with the local case by generating duplicate versions

View File

@ -1220,7 +1220,7 @@ package body Exp_Util is
Constraints => New_List
(New_Reference_To (Slice_Type, Loc)))));
-- This subtype indication may be used later for contraint checks
-- This subtype indication may be used later for constraint checks
-- we better make sure that if a variable was used as a bound of
-- of the original slice, its value is frozen.
@ -1657,7 +1657,7 @@ package body Exp_Util is
begin
-- Climb to the root type
-- Handle sychronized interface derivations
-- Handle synchronized interface derivations
if Is_Concurrent_Record_Type (Typ) then
declare
@ -2121,7 +2121,7 @@ package body Exp_Util is
if N = CV then
Sens := True;
-- Otherwise we must be in susbequent ELSIF or ELSE part
-- Otherwise we must be in subsequent ELSIF or ELSE part
else
Sens := False;
@ -2861,7 +2861,7 @@ package body Exp_Util is
-- This is the proper body corresponding to a stub. Insertion
-- must be done at the point of the stub, which is in the decla-
-- tive part of the parent unit.
-- rative part of the parent unit.
P := Corresponding_Stub (Parent (N));
@ -3704,7 +3704,7 @@ package body Exp_Util is
-- Generate the following code:
-- type Equiv_T is record
-- _parent : T (List of discriminant constaints taken from Exp);
-- _parent : T (List of discriminant constraints taken from Exp);
-- Ext__50 : Storage_Array (1 .. (Exp'size - Typ'object_size)/8);
-- end Equiv_T;
--
@ -3917,8 +3917,8 @@ package body Exp_Util is
-- Make_Subtype_From_Expr --
----------------------------
-- 1. If Expr is an uncontrained array expression, creates
-- Unc_Type(Expr'first(1)..Expr'Last(1),..., Expr'first(n)..Expr'last(n))
-- 1. If Expr is an unconstrained array expression, creates
-- Unc_Type(Expr'first(1)..Expr'last(1),..., Expr'first(n)..Expr'last(n))
-- 2. If Expr is a unconstrained discriminated type expression, creates
-- Unc_Type(Expr.Discr1, ... , Expr.Discr_n)
@ -4307,7 +4307,7 @@ package body Exp_Util is
-- this may happen with any array or record type. On the other hand, we
-- cannot create temporaries for all expressions for which this
-- condition is true, for various reasons that might require clearing up
-- ??? For example, descriminant references that appear out of place, or
-- ??? For example, discriminant references that appear out of place, or
-- spurious type errors with class-wide expressions. As a result, we
-- limit the transformation to loop bounds, which is so far the only
-- case that requires it.
@ -4420,9 +4420,9 @@ package body Exp_Util is
elsif Compile_Time_Known_Value (N) then
return True;
-- A variable renaming is not side-effet free, because the
-- A variable renaming is not side-effect free, because the
-- renaming will function like a macro in the front-end in
-- some cases, and an assignment can modify the the component
-- some cases, and an assignment can modify the component
-- designated by N, so we need to create a temporary for it.
elsif Is_Entity_Name (Original_Node (N))
@ -5247,7 +5247,7 @@ package body Exp_Util is
Long_Integer_Sized_Small : Ureal;
-- Set to 2.0 ** -(Long_Integer'Size - 1) the first time that this
-- functoin is called (we don't want to compute it more than once)
-- function is called (we don't want to compute it more than once)
First_Time_For_THFO : Boolean := True;
-- Set to False after first call (if Fractional_Fixed_Ops_On_Target)

View File

@ -258,7 +258,7 @@ package Exp_Util is
-- System_Tasking_Protected_Objects_Single_Entry
function Current_Sem_Unit_Declarations return List_Id;
-- Return the a place where it is fine to insert declarations for the
-- Return the place where it is fine to insert declarations for the
-- current semantic unit. If the unit is a package body, return the
-- visible declarations of the corresponding spec. For RCI stubs, this
-- is necessary because the point at which they are generated may not
@ -429,7 +429,7 @@ package Exp_Util is
-- homonym number used to disambiguate overloaded subprograms in the same
-- scope (the number is used as part of constructed names to make sure that
-- they are unique). The number is the ordinal position on the Homonym
-- chain, counting only entries in the curren scope. If an entity is not
-- chain, counting only entries in the current scope. If an entity is not
-- overloaded, the returned number will be one.
function Inside_Init_Proc return Boolean;
@ -437,7 +437,7 @@ package Exp_Util is
function In_Unconditional_Context (Node : Node_Id) return Boolean;
-- Node is the node for a statement or a component of a statement. This
-- function deteermines if the statement appears in a context that is
-- function determines if the statement appears in a context that is
-- unconditionally executed, i.e. it is not within a loop or a conditional
-- or a case statement etc.

View File

@ -242,7 +242,7 @@ package body Exp_VFpt is
Func : RE_Id;
function Call_Type (T : Entity_Id; Otyp : Entity_Id) return RE_Id;
-- Given one of the two types T, determines the coresponding call
-- Given one of the two types T, determines the corresponding call
-- type, i.e. the type to be used for the call (or the result of
-- the call). The actual operand is converted to (or from) this type.
-- Otyp is the other type, which is useful in figuring out the result.

View File

@ -331,7 +331,7 @@ package body Freeze is
begin
-- The controlling formal may be an access parameter, or the
-- actual may be an access value, so ajust accordingly.
-- actual may be an access value, so adjust accordingly.
if Is_Access_Type (Pref_Type)
and then not Is_Access_Type (Form_Type)
@ -791,7 +791,7 @@ package body Freeze is
-- discriminant.
-- This is because gigi computes the size by doing a
-- substituation of the appropriate discriminant value in
-- substitution of the appropriate discriminant value in
-- the size expression for the base type, and gigi is not
-- clever enough to evaluate the resulting expression (which
-- involves a call to rep_to_pos) at compile time.
@ -2915,7 +2915,7 @@ package body Freeze is
-- processing is only done for base types, since all the
-- representation aspects involved are type-related. This
-- is not just an optimization, if we start processing the
-- subtypes, they intefere with the settings on the base
-- subtypes, they interfere with the settings on the base
-- type (this is because Is_Packed has a slightly different
-- meaning before and after freezing).
@ -3222,7 +3222,7 @@ package body Freeze is
Freeze_Record_Type (E);
-- For a concurrent type, freeze corresponding record type. This
-- does not correpond to any specific rule in the RM, but the
-- does not correspond to any specific rule in the RM, but the
-- record type is essentially part of the concurrent type.
-- Freeze as well all local entities. This includes record types
-- created for entry parameter blocks, and whatever local entities
@ -3636,7 +3636,7 @@ package body Freeze is
if Has_Size_Clause (E)
and then not Size_Known_At_Compile_Time (E)
then
-- Supress this message if errors posted on E, even if we are
-- Suppress this message if errors posted on E, even if we are
-- in all errors mode, since this is often a junk message
if not Error_Posted (E) then
@ -4047,7 +4047,7 @@ package body Freeze is
and then Is_Enumeration_Type (Etype (N))
then
-- If enumeration literal appears directly as the choice,
-- do not freeze (this is the normal non-overloade case)
-- do not freeze (this is the normal non-overloaded case)
if Nkind (Parent (N)) = N_Component_Association
and then First (Choices (Parent (N))) = N
@ -4410,7 +4410,7 @@ package body Freeze is
-- case of both bounds negative, because the sign will be dealt
-- with anyway. Furthermore we can't just go making such a bound
-- symmetrical, since in a twos-complement system, there is an
-- extra negative value which could not be accomodated on the
-- extra negative value which could not be accommodated on the
-- positive side.
if Typ = Btyp

View File

@ -178,7 +178,7 @@ package Freeze is
procedure Expand_Atomic_Aggregate (E : Entity_Id; Typ : Entity_Id);
-- If an atomic object is initialized with an aggregate or is assigned
-- an aggregate, we have to prevent a piecemeal access or assignment
-- to the object, even if the aggregate is to be expanded. we create
-- to the object, even if the aggregate is to be expanded. We create
-- a temporary for the aggregate, and assign the temporary instead,
-- so that the back end can generate an atomic move for it.

View File

@ -103,7 +103,7 @@ begin
end if;
-- Now that the preprocessing situation is established, we are able to
-- load the main source (this is no longer done by Lib.Load.Initalize).
-- load the main source (this is no longer done by Lib.Load.Initialize).
Lib.Load.Load_Main_Source;
@ -355,7 +355,7 @@ begin
Sprint.Source_Dump;
-- If a mapping file has been specified by a -gnatem switch, update
-- it if there has been some sourcs that were not in the mappings.
-- it if there has been some sources that were not in the mappings.
if Mapping_File_Name /= null then
Fmap.Update_Mapping_File (Mapping_File_Name.all);

View File

@ -1864,7 +1864,7 @@ package body GNAT.Altivec.Low_Level_Vectors is
function To_Pixel (Source : unsigned_short) return Pixel_16 is
-- This conversion should not depend on the host endianess;
-- This conversion should not depend on the host endianness;
-- therefore, we cannot use an unchecked conversion.
Target : Pixel_16;
@ -1879,7 +1879,7 @@ package body GNAT.Altivec.Low_Level_Vectors is
function To_Pixel (Source : unsigned_int) return Pixel_32 is
-- This conversion should not depend on the host endianess;
-- This conversion should not depend on the host endianness;
-- therefore, we cannot use an unchecked conversion.
Target : Pixel_32;
@ -1898,10 +1898,10 @@ package body GNAT.Altivec.Low_Level_Vectors is
function To_unsigned_int (Source : Pixel_32) return unsigned_int is
-- This conversion should not depend on the host endianess;
-- This conversion should not depend on the host endianness;
-- therefore, we cannot use an unchecked conversion.
-- It should also be the same result, value-wise, on two hosts
-- with the same endianess.
-- with the same endianness.
Target : unsigned_int := 0;
@ -1930,10 +1930,10 @@ package body GNAT.Altivec.Low_Level_Vectors is
function To_unsigned_short (Source : Pixel_16) return unsigned_short is
-- This conversion should not depend on the host endianess;
-- This conversion should not depend on the host endianness;
-- therefore, we cannot use an unchecked conversion.
-- It should also be the same result, value-wise, on two hosts
-- with the same endianess.
-- with the same endianness.
Target : unsigned_short := 0;
@ -2765,9 +2765,9 @@ package body GNAT.Altivec.Low_Level_Vectors is
-- ??? Check the precision of the operation.
-- As described in [PEM-6 vexptefp]:
-- If theorical_result is equal to 2 at the power of A (J) with
-- If theoretical_result is equal to 2 at the power of A (J) with
-- infinite precision, we should have:
-- abs ((D (J) - theorical_result) / theorical_result) <= 1/16
-- abs ((D (J) - theoretical_result) / theoretical_result) <= 1/16
D.Values (J) := 2.0 ** NJ_Truncate (VA.Values (J));
end loop;

View File

@ -37,7 +37,7 @@ with System; use System;
package body GNAT.Altivec.Conversions is
-- All the vector/view conversions operate similarily: bare unchecked
-- All the vector/view conversions operate similarly: bare unchecked
-- conversion on big endian targets, and elements permutation on little
-- endian targets. We call "Mirroring" the elements permutation process.

View File

@ -135,7 +135,7 @@
-- of driving ideas:
-- o From the clients standpoint, the two versions of the binding should be
-- as easily exchangable as possible,
-- as easily exchangeable as possible,
-- o From the maintenance standpoint, we want to avoid as much code
-- duplication as possible.

View File

@ -8097,7 +8097,7 @@ private
pragma Inline_Always (vec_any_numeric);
pragma Inline_Always (vec_any_out);
-- Similarily, vec_step is expected to be turned into a compile time
-- Similarly, vec_step is expected to be turned into a compile time
-- constant, so ...
pragma Inline_Always (vec_step);

View File

@ -38,7 +38,7 @@
-- Accessing vector contents with direct memory overlays should be avoided
-- because actual vector representations may vary across configurations, for
-- instance to accomodate different target endianness.
-- instance to accommodate different target endianness.
-- The natural representation of a vector is an array indexed by vector
-- component number, which is materialized by the Varray type definitions

View File

@ -47,8 +47,8 @@ package body GNAT.Array_Split is
function Count
(Source : Element_Sequence;
Pattern : Element_Set) return Natural;
-- Returns the number of occurences of Pattern elements in Source, 0 is
-- returned if no occurence is found in Source.
-- Returns the number of occurrences of Pattern elements in Source, 0 is
-- returned if no occurrence is found in Source.
------------
-- Adjust --

View File

@ -43,7 +43,7 @@
-- There is also GNAT.Bubble_Sort_A, which is now considered obsolete, but
-- was an older version working with subprogram parameters. This version
-- is retained for baccwards compatibility with old versions of GNAT.
-- is retained for backwards compatibility with old versions of GNAT.
generic
-- The data to be sorted is assumed to be indexed by integer values from

View File

@ -307,7 +307,7 @@ package body GNAT.Calendar is
pragma Unreferenced (Hour, Minute, Second, Sub_Second);
function Is_Leap (Year : Year_Number) return Boolean;
-- Return True if Year denotes a leap year. Leap centential years are
-- Return True if Year denotes a leap year. Leap centennial years are
-- properly handled.
function Jan_1_Day_Of_Week

View File

@ -39,7 +39,7 @@
-- Ada.Calendar. It provides Split and Time_Of to build and split a Time
-- data. And it provides accessor functions to get only one of Hour, Minute,
-- Second, Second_Duration. Other functions are to access more advanced
-- valueas like Day_Of_Week, Day_In_Year and Week_In_Year.
-- values like Day_Of_Week, Day_In_Year and Week_In_Year.
with Ada.Calendar;
with Interfaces.C;
@ -64,7 +64,7 @@ package GNAT.Calendar is
function Minute (Date : Ada.Calendar.Time) return Minute_Number;
function Second (Date : Ada.Calendar.Time) return Second_Number;
function Sub_Second (Date : Ada.Calendar.Time) return Second_Duration;
-- Hour, Minute, Sedond and Sub_Second returns the complete time data for
-- Hour, Minute, Second and Sub_Second returns the complete time data for
-- the Date (H:M:S.SS). See Ada.Calendar for Year, Month, Day accessors.
-- Second_Duration precision depends on the target clock precision.

View File

@ -59,7 +59,7 @@ package GNAT.Case_Util is
procedure To_Upper (A : in out String)
renames System.Case_Util.To_Upper;
-- Folds all characters of string A to upper csae
-- Folds all characters of string A to upper case
function To_Lower (A : Character) return Character
renames System.Case_Util.To_Lower;

View File

@ -41,7 +41,7 @@ package body GNAT.CGI.Debug is
-- To create a new IO mode you must:
-- 1. create a new package spec
-- 2. create a new type derived from IO.Format
-- 3. implement all the abstract rountines in IO
-- 3. implement all the abstract routines in IO
package IO is

View File

@ -43,7 +43,7 @@ package body GNAT.Command_Line is
Parameter_With_Optional_Space, -- ':' in getopt
Parameter_With_Space_Or_Equal, -- '=' in getopt
Parameter_No_Space, -- '!' in getopt
Parameter_Optional); -- '?' in getop
Parameter_Optional); -- '?' in getopt
procedure Set_Parameter
(Variable : out Parameter_Type;
@ -134,7 +134,7 @@ package body GNAT.Command_Line is
(Cmd : Command_Line;
Result : Argument_List_Access;
Params : Argument_List_Access);
-- When possible, replace or more switches by an alias, ie a shorter
-- When possible, replace or more switches by an alias, i.e. a shorter
-- version.
function Looking_At
@ -567,7 +567,7 @@ package body GNAT.Command_Line is
-- Always prepend the switch character, so that users know that
-- this comes from a switch on the command line. This is
-- especially important when Concatenate is False, since
-- otherwise the currrent argument first character is lost.
-- otherwise the current argument first character is lost.
Set_Parameter
(Parser.The_Switch,

View File

@ -42,7 +42,7 @@
-- (special command line arguments starting with '-' by default) and their
-- parameters, and then the rest of the command line arguments.
-- This package is flexible enough to accomodate various needs: optional
-- This package is flexible enough to accommodate various needs: optional
-- switch parameters, various characters to separate a switch and its
-- parameter, whether to stop the parsing at the first non-switch argument
-- encountered, etc.
@ -84,7 +84,7 @@
-- A more complicated example would involve the use of sections for the
-- switches, as for instance in gnatmake. The same command line is used to
-- provide switches for several tools. Each tool recognizes its switches by
-- separating them with special switches, chosen by the programer.
-- separating them with special switches, chosen by the programmer.
-- Each section acts as a command line of its own.
-- begin
@ -401,7 +401,7 @@ package GNAT.Command_Line is
-- matching switch is returned.
--
-- Arbitrary characters are allowed for switches, although it is
-- strongly recommanded to use only letters and digits for portability
-- strongly recommended to use only letters and digits for portability
-- reasons.
--
-- When Concatenate is False, individual switches need to be separated by

View File

@ -50,7 +50,7 @@ package GNAT.Current_Exception is
-- Subprograms --
-----------------
-- Note: the lower bound of returnd String values is always one
-- Note: the lower bound of returned String values is always one
function Exception_Information return String;
-- Returns the result of calling Ada.Exceptions.Exception_Information
@ -95,7 +95,7 @@ package GNAT.Current_Exception is
-- For greater compatibility with existing legacy software, library
-- level renaming may be used to create a function with a name matching
-- one that is in use. For example, some versions of VADS Ada provided
-- a functin called Current_Exception whose semantics was identical to
-- a function called Current_Exception whose semantics was identical to
-- that of GNAT. The following library level renaming declaration:
-- with GNAT.Current_Exception;

View File

@ -49,7 +49,7 @@ package body GNAT.Debug_Pools is
Default_Alignment : constant := Standard'Maximum_Alignment;
-- Alignment used for the memory chunks returned by Allocate. Using this
-- value garantees that this alignment will be compatible with all types
-- value guarantees that this alignment will be compatible with all types
-- and at the same time makes it easy to find the location of the extra
-- header allocated for each chunk.
@ -286,10 +286,10 @@ package body GNAT.Debug_Pools is
Ignored_Frame_Start : System.Address;
Ignored_Frame_End : System.Address);
-- Set Start .. Len to the range of values from Trace that should be output
-- to the user. This range of values exludes any address prior to the first
-- one in Ignored_Frame_Start .. Ignored_Frame_End (basically addresses
-- internal to this package). Depth is the number of levels that the user
-- is interested in.
-- to the user. This range of values excludes any address prior to the
-- first one in Ignored_Frame_Start .. Ignored_Frame_End (basically
-- addresses internal to this package). Depth is the number of levels that
-- the user is interested in.
---------------
-- Header_Of --
@ -579,7 +579,7 @@ package body GNAT.Debug_Pools is
begin
-- The pool only returns addresses aligned on Default_Alignment so
-- anything off cannot be a valid block address and we can return
-- early in this case. We actually have to since our datastructures
-- early in this case. We actually have to since our data structures
-- map validity bits for such aligned addresses only.
if Int_Storage mod Default_Alignment /= 0 then
@ -692,7 +692,7 @@ package body GNAT.Debug_Pools is
Free_Physically (Pool);
end if;
-- Use standard (ie through malloc) allocations. This automatically
-- Use standard (i.e. through malloc) allocations. This automatically
-- raises Storage_Error if needed. We also try once more to physically
-- release memory, so that even marked blocks, in the advanced scanning,
-- are freed.

View File

@ -253,7 +253,7 @@ package GNAT.Debug_Pools is
-- the Debug_Pool).
--
-- The information includes the stacktrace for the allocation or
-- deallocation of that memory chunck, its current status (allocated or
-- deallocation of that memory chunk, its current status (allocated or
-- logically freed), etc.
private
@ -288,7 +288,7 @@ private
Storage_Address : System.Address;
Size_In_Storage_Elements : Storage_Count;
Alignment : Storage_Count);
-- Check whether a derefence statement is valid, ie whether the pointer
-- Check whether a dereference statement is valid, i.e. whether the pointer
-- was allocated through Pool. As documented above, errors will be
-- reported either by a special error message or an exception, depending
-- on the setup of the storage pool.
@ -296,7 +296,7 @@ private
type Byte_Count is mod System.Max_Binary_Modulus;
-- Type used for maintaining byte counts, needs to be large enough
-- to accomodate counts allowing for repeated use of the same memory.
-- to accommodate counts allowing for repeated use of the same memory.
type Debug_Pool is new System.Checked_Pools.Checked_Pool with record
Stack_Trace_Depth : Natural := Default_Stack_Trace_Depth;
@ -322,7 +322,7 @@ private
Marked_Blocks_Deallocated : Boolean := False;
-- Set to true if some mark blocks had to be deallocated in the advanced
-- scanning scheme. Since this is potentially dangereous, this is
-- scanning scheme. Since this is potentially dangerous, this is
-- reported to the user, who might want to rerun his program with a
-- lower Minimum_To_Free value.

View File

@ -391,7 +391,7 @@ package body GNAT.Decode_String is
end if;
end UTF8;
-- Non-UTF-8 cass
-- Non-UTF-8 case
else
declare
@ -502,7 +502,7 @@ package body GNAT.Decode_String is
end if;
end UTF8;
-- Non-UTF-8 cass
-- Non-UTF-8 case
else
declare

View File

@ -415,7 +415,7 @@ package body GNAT.Directory_Operations is
E := K;
-- Check that first chartacter is a letter
-- Check that first character is a letter
if Characters.Handling.Is_Letter (Path (E)) then
E := E + 1;

View File

@ -223,7 +223,7 @@ package GNAT.Directory_Operations is
-- Dir will be set to Null_Dir.
procedure Close (Dir : in out Dir_Type);
-- Closes the directory stream refered to by Dir. After calling Close
-- Closes the directory stream referred to by Dir. After calling Close
-- Is_Open will return False. Dir will be set to Null_Dir.
-- Raises Directory_Error if Dir has not be opened (Dir = Null_Dir).

View File

@ -130,7 +130,7 @@ package GNAT.Dynamic_HTables is
function Get_Next (T : Instance) return Elmt_Ptr;
-- Returns a non-specified element that has not been returned by the
-- same function since the last call to Get_First or Null_Ptr if
-- there is no such element or Get_First has bever been called. If
-- there is no such element or Get_First has never been called. If
-- there is no call to 'Set' in between Get_Next calls, all the
-- elements of the Htable will be traversed.

View File

@ -257,7 +257,7 @@ package body GNAT.Dynamic_Tables is
-- checks are suppressed because this unit uses direct calls to
-- System.Memory for allocation, and this can yield misaligned storage
-- (and we cannot rely on the bootstrap compiler supporting specifically
-- disabling alignment cheks, so we need to suppress all range checks).
-- disabling alignment checks, so we need to suppress all range checks).
-- It is safe to suppress this check here because we know that a
-- (possibly misaligned) object of that type does actually exist at that
-- address.
@ -269,7 +269,7 @@ package body GNAT.Dynamic_Tables is
-- involve moving table contents around).
begin
-- If we're going to reallocate, check wheter Item references an
-- If we're going to reallocate, check whether Item references an
-- element of the currently allocated table.
if Need_Realloc

View File

@ -35,7 +35,7 @@
-- Wide_String or Wide_Wide_String to encoded String using a specified
-- encoding convention, which is supplied as the generic parameter. If
-- this parameter is a known at compile time constant (e.g. a constant
-- definned in System.WCh_Con), the instantiation is specialized so that
-- defined in System.WCh_Con), the instantiation is specialized so that
-- it applies only to this specified coding.
-- Note: this package is only about encoding sequences of 16- or 32-bit
@ -66,7 +66,7 @@ package GNAT.Encode_String is
pragma Inline (Encode_Wide_String);
-- Encode the given Wide_String, returning a String encoded using the
-- given encoding method. Constraint_Error will be raised if the encoding
-- method cannot accomodate the input data.
-- method cannot accommodate the input data.
procedure Encode_Wide_String
(S : Wide_String;
@ -78,7 +78,7 @@ package GNAT.Encode_String is
-- in System.WCh_Con: WC_Longest_Sequence, WC_Longest_Sequences). If the
-- length of Result is insufficient Constraint_Error will be raised.
-- Constraint_Error will also be raised if the encoding method cannot
-- accomodate the input data.
-- accommodate the input data.
function Encode_Wide_Wide_String (S : Wide_Wide_String) return String;
pragma Inline (Encode_Wide_Wide_String);
@ -98,8 +98,8 @@ package GNAT.Encode_String is
-- This is a lower level procedure that encodes the single character Char.
-- The output is stored in Result starting at Result (Ptr), and Ptr is
-- updated past the stored value. Constraint_Error is raised if Result
-- is not long enough to accomodate the result, or if the encoding method
-- specified does not accomodate the input character value, or if Ptr is
-- is not long enough to accommodate the result, or if the encoding method
-- specified does not accommodate the input character value, or if Ptr is
-- outside the bounds of the Result string.
procedure Encode_Wide_Wide_Character

View File

@ -35,7 +35,7 @@
-- These callbacks are called immediately when either a specific exception,
-- or any exception, is raised, before any other actions taken by raise, in
-- particular before any unwinding of the stack occcurs.
-- particular before any unwinding of the stack occurs.
-- Callbacks for specific exceptions are registered through calls to
-- Register_Id_Action. Here is an example of code that uses this package to

View File

@ -39,7 +39,7 @@
-- However, it is not normally possible to raise an exception with a
-- message because the routine Ada.Exceptions.Raise_Exception is not in
-- a Pure unit. This is an annoying and unnecessary restrictiona and this
-- a Pure unit. This is an annoying and unnecessary restriction and this
-- package allows for raising the standard predefined exceptions at least.
package GNAT.Exceptions is

View File

@ -176,7 +176,7 @@ package GNAT.Expect is
-- this buffer is full. Beware that if the buffer is too big, this could
-- slow down the Expect calls if not output is matched, since Expect has
-- to match all the regexp against all the characters in the buffer.
-- If Buffer_Size is 0, there is no limit (ie all the characters are kept
-- If Buffer_Size is 0, there is no limit (i.e. all the characters are kept
-- till Expect matches), but this is slower.
--
-- If Err_To_Out is True, then the standard error of the spawned process is
@ -221,7 +221,7 @@ package GNAT.Expect is
function Get_Pid
(Descriptor : Process_Descriptor) return Process_Id;
-- Return the process id assocated with a given process descriptor
-- Return the process id associated with a given process descriptor
function Get_Command_Output
(Command : String;
@ -410,7 +410,7 @@ package GNAT.Expect is
return Pattern_Matcher_Access;
-- Allocate some memory for the pattern matcher.
-- This is only a convenience function to help create the array of
-- compiled regular expressoins.
-- compiled regular expressions.
procedure Expect
(Descriptor : in out Process_Descriptor;

View File

@ -74,7 +74,7 @@ package body GNAT.Heap_Sort is
-- we assume that the current node will be less than the larger
-- son, and unconditionally sift up. Then when we get to the bottom
-- of the tree, we check parents to make sure that we did not make
-- a mistake. This roughly cuts the number of comparisions in half,
-- a mistake. This roughly cuts the number of comparisons in half,
-- since it is almost always the case that our assumption is correct.
-- Loop to pull up larger sons

View File

@ -76,7 +76,7 @@ package body GNAT.Heap_Sort_A is
-- we assume that the current node will be less than the larger
-- son, and unconditionally sift up. Then when we get to the bottom
-- of the tree, we check parents to make sure that we did not make
-- a mistake. This roughly cuts the number of comparisions in half,
-- a mistake. This roughly cuts the number of comparisons in half,
-- since it is almost always the case that our assumption is correct.
-- Loop to pull up larger sons

View File

@ -79,7 +79,7 @@ package body GNAT.Heap_Sort_G is
-- we assume that the current node will be less than the larger
-- son, and unconditionally sift up. Then when we get to the bottom
-- of the tree, we check parents to make sure that we did not make
-- a mistake. This roughly cuts the number of comparisions in half,
-- a mistake. This roughly cuts the number of comparisons in half,
-- since it is almost always the case that our assumption is correct.
-- Loop to pull up larger sons

View File

@ -196,7 +196,7 @@ package GNAT.HTable is
-- function Get_Next return Elmt_Ptr;
-- -- Returns a non-specified element that has not been returned by
-- -- the same function since the last call to Get_First or Null_Ptr
-- -- if there is no such element or Get_First has bever been called.
-- -- if there is no such element or Get_First has never been called.
-- -- If there is no call to 'Set' in between Get_Next calls, all
-- -- the elements of the HTable will be traversed.

View File

@ -32,7 +32,7 @@
------------------------------------------------------------------------------
-- This package contains the necessary routines for using files for the
-- purpose of providing realiable system wide locking capability.
-- purpose of providing reliable system wide locking capability.
package GNAT.Lock_Files is
pragma Preelaborate;

View File

@ -46,7 +46,7 @@ package body GNAT.MD5 is
-- Look-up table for each hex digit of the Message-Digest.
-- Used by function Digest (Context).
-- The sixten values used to rotate the context words.
-- The sixteen values used to rotate the context words.
-- Four for each rounds. Used in procedure Transform.
-- Round 1

View File

@ -36,7 +36,7 @@
--
-- http://www.ietf.org/rfc/rfc1321.txt
--
-- The implementation is derived from the RSA Data Secutity, Inc. MD5
-- The implementation is derived from the RSA Data Security, Inc. MD5
-- Message-Digest Algorithm, as described in RFC 1321.
with Ada.Streams;

View File

@ -46,7 +46,7 @@ package GNAT.Memory_Dump is
-- case of a byte addressable machine (and is therefore inapplicable to
-- machines like the AAMP, where the storage unit is not 8 bits). The
-- output is one or more lines in the following format, which is for the
-- case of 32-bit addresses (64-bit addressea are handled appropriately):
-- case of 32-bit addresses (64-bit addresses are handled appropriately):
--
-- 0234_3368: 66 67 68 . . . 73 74 75 "fghijklmnopqstuv"
--

View File

@ -33,7 +33,7 @@
-- This package provides routines for accessing the most recently raised
-- exception. This may be useful for certain logging activities. It may
-- also be useful for mimicing implementation dependent capabilities in
-- also be useful for mimicking implementation dependent capabilities in
-- Ada 83 compilers, but see also GNAT.Current_Exceptions for this usage.
with Ada.Exceptions;

View File

@ -33,6 +33,6 @@
-- This package does not require a body, since it is a package renaming. We
-- provide a dummy file containing a No_Body pragma so that previous versions
-- of the body (which did exist) will not intefere.
-- of the body (which did exist) will not interfere.
pragma No_Body;

View File

@ -74,7 +74,7 @@ package body GNAT.Perfect_Hash_Generators is
-- Random graphs are frequently used to solve difficult problems that do
-- not have polynomial solutions. This algorithm is based on a weighted
-- undirected graph. It comprises two steps: mapping and assigment.
-- undirected graph. It comprises two steps: mapping and assignment.
-- In the mapping step, a graph G = (V, E) is constructed, where = {0, 1,
-- ..., n-1} and E = {(for w in W) (f1 (w), f2 (w))}. In order for the
@ -588,7 +588,7 @@ package body GNAT.Perfect_Hash_Generators is
-- Start of processing for Assign_Values_To_Vertices
begin
-- Value -1 denotes an unitialized value as it is supposed to
-- Value -1 denotes an uninitialized value as it is supposed to
-- be in the range 0 .. NK.
if G = No_Table then
@ -2144,7 +2144,7 @@ package body GNAT.Perfect_Hash_Generators is
loop
-- Preserve maximum number of different keys and check later on
-- that this value is strictly incrementing. Otherwise, it means
-- that two keys are stricly identical.
-- that two keys are strictly identical.
Old_Differences := Max_Differences;

View File

@ -62,7 +62,7 @@
-- The functions generated by this package require the key set to be known in
-- advance (they are "static" hash functions). The hash functions are also
-- order preservering. If w2 is inserted after w1 in the generator, then (w1)
-- order preserving. If w2 is inserted after w1 in the generator, then (w1)
-- < f (w2). These hashing functions are convenient for use with realtime
-- applications.
@ -71,7 +71,7 @@ package GNAT.Perfect_Hash_Generators is
Default_K_To_V : constant Float := 2.05;
-- Default ratio for the algorithm. When K is the number of keys, V =
-- (K_To_V) * K is the size of the main table of the hash function. To
-- converge, the algorithm requires K_To_V to be stricly greater than 2.0.
-- converge, the algorithm requires K_To_V to be strictly greater than 2.0.
Default_Pkg_Name : constant String := "Perfect_Hash";
-- Default package name in which the hash function is defined
@ -113,7 +113,7 @@ package GNAT.Perfect_Hash_Generators is
-- Insert a new key in the table
Too_Many_Tries : exception;
-- Raised after Tries unsuccessfull runs
-- Raised after Tries unsuccessful runs
procedure Compute (Position : String := Default_Position);
-- Compute the hash function. Position allows to define selection of

View File

@ -33,6 +33,6 @@
-- This package does not require a body, since it is a package renaming. We
-- provide a dummy file containing a No_Body pragma so that previous versions
-- of the body (which did exist) will not intefere.
-- of the body (which did exist) will not interfere.
pragma No_Body;

View File

@ -43,7 +43,7 @@
-- Summary of Pattern Matching Packages in GNAT Hierarchy --
------------------------------------------------------------
-- There are three related packages that perform pattern maching functions.
-- There are three related packages that perform pattern matching functions.
-- the following is an outline of these packages, to help you determine
-- which is best for your needs.
@ -62,7 +62,7 @@
-- stored in a binary compatible manner.
-- GNAT.Spitbol.Patterns (files g-spipat.ads/g-spipat.adb)
-- This is a completely general patterm matching package based on the
-- This is a completely general pattern matching package based on the
-- pattern language of SNOBOL4, as implemented in SPITBOL. The pattern
-- language is modeled on context free grammars, with context sensitive
-- extensions that provide full (type 0) computational capabilities.

View File

@ -34,6 +34,6 @@
-- This package does not require a body, since it is a package renaming. We
-- provide a dummy file containing a No_Body pragma so that previous versions
-- of the body (which did exist) will not intefere.
-- of the body (which did exist) will not interfere.
pragma No_Body;

View File

@ -46,7 +46,7 @@
-- Summary of Pattern Matching Packages in GNAT Hierarchy --
------------------------------------------------------------
-- There are three related packages that perform pattern maching functions.
-- There are three related packages that perform pattern matching functions.
-- the following is an outline of these packages, to help you determine
-- which is best for your needs.

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 75; -- Socket already connected
ELOOP : constant := 85; -- Too many symbolic lynks
ELOOP : constant := 85; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 59; -- Message too long
ENAMETOOLONG : constant := 86; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 56; -- Socket already connected
ELOOP : constant := 62; -- Too many symbolic lynks
ELOOP : constant := 62; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 40; -- Message too long
ENAMETOOLONG : constant := 63; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 56; -- Socket already connected
ELOOP : constant := 62; -- Too many symbolic lynks
ELOOP : constant := 62; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 40; -- Message too long
ENAMETOOLONG : constant := 63; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 234; -- Socket already connected
ELOOP : constant := 249; -- Too many symbolic lynks
ELOOP : constant := 249; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 218; -- Message too long
ENAMETOOLONG : constant := 248; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 234; -- Socket already connected
ELOOP : constant := 249; -- Too many symbolic lynks
ELOOP : constant := 249; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 218; -- Message too long
ENAMETOOLONG : constant := 248; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 133; -- Socket already connected
ELOOP : constant := 90; -- Too many symbolic lynks
ELOOP : constant := 90; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 97; -- Message too long
ENAMETOOLONG : constant := 78; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 106; -- Socket already connected
ELOOP : constant := 40; -- Too many symbolic lynks
ELOOP : constant := 40; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 90; -- Message too long
ENAMETOOLONG : constant := 36; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 106; -- Socket already connected
ELOOP : constant := 40; -- Too many symbolic lynks
ELOOP : constant := 40; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 90; -- Message too long
ENAMETOOLONG : constant := 36; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 106; -- Socket already connected
ELOOP : constant := 40; -- Too many symbolic lynks
ELOOP : constant := 40; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 90; -- Message too long
ENAMETOOLONG : constant := 36; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 106; -- Socket already connected
ELOOP : constant := 40; -- Too many symbolic lynks
ELOOP : constant := 40; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 90; -- Message too long
ENAMETOOLONG : constant := 36; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 10022; -- Invalid argument
EIO : constant := 10101; -- Input output error
EISCONN : constant := 10056; -- Socket already connected
ELOOP : constant := 10062; -- Too many symbolic lynks
ELOOP : constant := 10062; -- Too many symbolic links
EMFILE : constant := 10024; -- Too many open files
EMSGSIZE : constant := 10040; -- Message too long
ENAMETOOLONG : constant := 10063; -- Name too long
@ -195,7 +195,7 @@ package GNAT.Sockets.Constants is
WSASYSNOTREADY : constant := 10091; -- System not ready
WSAVERNOTSUPPORTED : constant := 10092; -- Version not supported
WSANOTINITIALISED : constant := 10093; -- Winsock not intialized
WSANOTINITIALISED : constant := 10093; -- Winsock not initialized
WSAEDISCON : constant := 10101; -- Disconnected
----------------------

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 133; -- Socket already connected
ELOOP : constant := 90; -- Too many symbolic lynks
ELOOP : constant := 90; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 97; -- Message too long
ENAMETOOLONG : constant := 78; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 133; -- Socket already connected
ELOOP : constant := 90; -- Too many symbolic lynks
ELOOP : constant := 90; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 97; -- Message too long
ENAMETOOLONG : constant := 78; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 56; -- Socket already connected
ELOOP : constant := 62; -- Too many symbolic lynks
ELOOP : constant := 62; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 40; -- Message too long
ENAMETOOLONG : constant := 63; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 56; -- Socket already connected
ELOOP : constant := 62; -- Too many symbolic lynks
ELOOP : constant := 62; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 40; -- Message too long
ENAMETOOLONG : constant := 63; -- Name too long

View File

@ -77,7 +77,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 56; -- Socket already connected
ELOOP : constant := 64; -- Too many symbolic lynks
ELOOP : constant := 64; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 36; -- Message too long
ENAMETOOLONG : constant := 26; -- Name too long

View File

@ -84,7 +84,7 @@ package GNAT.Sockets.Constants is
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 106; -- Socket already connected
ELOOP : constant := 40; -- Too many symbolic lynks
ELOOP : constant := 40; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 90; -- Message too long
ENAMETOOLONG : constant := 36; -- Name too long

View File

@ -61,7 +61,7 @@ package body GNAT.Sockets is
-- the operating system, or else return data through a user-provided buffer
-- to ensure concurrent uses do not interfere.
-- Correspondance tables
-- Correspondence tables
Families : constant array (Family_Type) of C.int :=
(Family_Inet => Constants.AF_INET,
@ -152,7 +152,7 @@ package body GNAT.Sockets is
function Network_To_Short
(S : C.unsigned_short) return C.unsigned_short
renames Short_To_Network;
-- Symetric operation
-- Symmetric operation
function Image
(Val : Inet_Addr_VN_Type;
@ -547,7 +547,7 @@ package body GNAT.Sockets is
Signalling_Fds.Close (C.int (Selector.W_Sig_Socket));
-- Reset R_Sig_Socket and W_Sig_Socket to No_Socket to ensure that any
-- (errneous) subsequent attempt to use this selector properly fails.
-- (erroneous) subsequent attempt to use this selector properly fails.
Selector.R_Sig_Socket := No_Socket;
Selector.W_Sig_Socket := No_Socket;

View File

@ -432,7 +432,7 @@ package GNAT.Sockets is
type Inet_Addr_Type (Family : Family_Type := Family_Inet) is private;
-- An Internet address depends on an address family (IPv4 contains 4
-- octets and Ipv6 contains 16 octets). Any_Inet_Addr is a special value
-- octets and IPv6 contains 16 octets). Any_Inet_Addr is a special value
-- treated like a wildcard enabling all addresses. No_Inet_Addr provides a
-- special value to denote uninitialized inet addresses.

View File

@ -303,7 +303,7 @@ package body GNAT.Sockets.Thin is
begin
-- Asynchronous connection failures are notified in the
-- exception fd set instead of the write fd set. To ensure
-- POSIX compatitibility, copy write fd set into exception fd
-- POSIX compatibility, copy write fd set into exception fd
-- set. Once select() returns, check any socket present in the
-- exception fd set and peek at incoming out-of-band data. If
-- the test is not successful, and the socket is present in

View File

@ -144,7 +144,7 @@ package body GNAT.Sockets.Thin is
if not Constants.Thread_Blocking_IO
and then R /= Failure
then
-- A socket inherits the properties ot its server especially
-- A socket inherits the properties of its server, especially
-- the FIONBIO flag. Do not use C_Ioctl as this subprogram
-- tracks sockets set in non-blocking mode by user.

View File

@ -156,7 +156,7 @@ package body GNAT.Sockets.Thin is
if not Constants.Thread_Blocking_IO
and then R /= Failure
then
-- A socket inherits the properties ot its server especially
-- A socket inherits the properties of its server especially
-- the FIONBIO flag. Do not use C_Ioctl as this subprogram
-- tracks sockets set in non-blocking mode by user.

View File

@ -32,7 +32,7 @@
------------------------------------------------------------------------------
-- This package is used to provide target specific linker_options for the
-- support of scokets as required by the package GNAT.Sockets.
-- support of sockets as required by the package GNAT.Sockets.
-- This is the Windows/NT version of this package

View File

@ -32,7 +32,7 @@
------------------------------------------------------------------------------
-- This package is used to provide target specific linker_options for the
-- support of scokets as required by the package GNAT.Sockets.
-- support of sockets as required by the package GNAT.Sockets.
-- This is the Solaris version of this package

View File

@ -32,7 +32,7 @@
------------------------------------------------------------------------------
-- This package is used to provide target specific linker_options for the
-- support of scokets as required by the package GNAT.Sockets.
-- support of sockets as required by the package GNAT.Sockets.
-- This is an empty version for default use where no additional libraries
-- are required. On some targets a target specific version of this unit

View File

@ -102,7 +102,7 @@ package body GNAT.Spitbol.Patterns is
-- I parameter(s) I
-- +------------------------------------+
-- Pcode is a code value indicating the type of the patterm node. This
-- Pcode is a code value indicating the type of the pattern node. This
-- code is used both as the discriminant value for the record, and as
-- the case index in the main match routine that branches to the proper
-- match code for the given element.
@ -113,7 +113,7 @@ package body GNAT.Spitbol.Patterns is
-- Pthen is a pointer to the successor node, i.e the node to be matched
-- if the attempt to match the node succeeds. If this is the last node
-- of the pattern to be matched, then Pthen points to a dummy node
-- of kind PC_EOP (end of pattern), which initiales pattern exit.
-- of kind PC_EOP (end of pattern), which initializes pattern exit.
-- The parameter or parameters are present for certain node types,
-- and the type varies with the pattern code.
@ -431,7 +431,7 @@ package body GNAT.Spitbol.Patterns is
---------------------------------------------------
-- The serial index numbers for the pattern elements are assigned as
-- a pattern is consructed from its constituent elements. Note that there
-- a pattern is constructed from its constituent elements. Note that there
-- is never any sharing of pattern elements between patterns (copies are
-- always made), so the serial index numbers are unique to a particular
-- pattern as referenced from the P field of a value of type Pattern.
@ -449,7 +449,7 @@ package body GNAT.Spitbol.Patterns is
-- pattern (e.g. copy and finalization processing). Once constructed
-- patterns are strictly read only. This is necessary to allow sharing
-- of patterns between tasks. This means that we cannot go marking the
-- pattern (e.g. with a visited bit). Instead we cosntuct a separate
-- pattern (e.g. with a visited bit). Instead we construct a separate
-- vector that contains the necessary information indexed by the Index
-- values in the pattern elements. For this purpose the only requirement
-- is that they be uniquely assigned.
@ -469,7 +469,7 @@ package body GNAT.Spitbol.Patterns is
-- Third, as compound pattern structures are constructed, the way in which
-- constituent parts of the pattern are constructed is stylized. This is
-- an automatic consequence of the way that these compounjd structures
-- an automatic consequence of the way that these compound structures
-- are constructed, and basically what we are doing is simply documenting
-- and specifying the natural result of the pattern construction. The
-- section describing compound pattern structures gives details of the
@ -588,7 +588,7 @@ package body GNAT.Spitbol.Patterns is
-- stack is used to control the backtracking. Finally, it notes the
-- way in which the Index numbers are assigned to the structure.
-- In all diagrams, solid lines (built witth minus signs or vertical
-- In all diagrams, solid lines (built with minus signs or vertical
-- bars, represent successor pointers (Pthen fields) with > or V used
-- to indicate the direction of the pointer. The initial node of the
-- structure is in the upper left of the diagram. A dotted line is an
@ -600,7 +600,7 @@ package body GNAT.Spitbol.Patterns is
-------------------
-- In the pattern structures listed in this section, a line that looks
-- lile ----> with nothing to the right indicates an end of pattern
-- like ----> with nothing to the right indicates an end of pattern
-- (EOP) pointer that represents the end of the match.
-- When a pattern concatenation (L & R) occurs, the resulting structure
@ -609,7 +609,7 @@ package body GNAT.Spitbol.Patterns is
-- occurs in constructing a pattern, and it means that the pattern
-- matching circuitry does not have to keep track of the structure
-- of a pattern with respect to concatenation, since the appropriate
-- succesor is always at hand.
-- successor is always at hand.
-- Concatenation itself generates no additional possibilities for
-- backtracking, but the constituent patterns of the concatenated
@ -643,7 +643,7 @@ package body GNAT.Spitbol.Patterns is
-- it stacks a pointer to the leading element of R on the history stack
-- so that on subsequent failure, a match of R is attempted.
-- The A node is the higest numbered element in the pattern. The
-- The A node is the highest numbered element in the pattern. The
-- original index numbers of R are unchanged, but the index numbers
-- of the L pattern are adjusted up by the count of elements in R.
@ -941,7 +941,7 @@ package body GNAT.Spitbol.Patterns is
-- described below.
-- It then stores a pointer to itself in the special entry node field.
-- This was otherwise unused, and is now used to retrive the address
-- This was otherwise unused, and is now used to retrieve the address
-- of the variable to be assigned at the end of the pattern.
-- After that the inner region is terminated in the usual manner,
@ -999,7 +999,7 @@ package body GNAT.Spitbol.Patterns is
-- string, starting at the current cursor position. It then updates
-- the cursor past this matched string, and stacks a pointer to itself
-- with this updated cursor value on the history stack, to extend the
-- matched string on a subequent failure.
-- matched string on a subsequent failure.
-- Since this is a single node it is numbered 1 (the reason we include
-- it in the compound patterns section is that it backtracks).
@ -1174,7 +1174,7 @@ package body GNAT.Spitbol.Patterns is
-- The following pattern elements are referenced only from the pattern
-- history stack. In each case the processing for the pattern element
-- results in pattern match abort, or futher failure, so there is no
-- results in pattern match abort, or further failure, so there is no
-- need for a successor and no need for a node number
CP_Assign : aliased PE := (PC_Assign, 0, N);
@ -1208,11 +1208,11 @@ package body GNAT.Spitbol.Patterns is
-- understand a typical use of this function).
function BreakX_Make (B : PE_Ptr) return Pattern;
-- Given a pattern element for a Break patternx, returns the
-- Given a pattern element for a Break pattern, returns the
-- corresponding BreakX compound pattern structure.
function Concat (L, R : PE_Ptr; Incr : Natural) return PE_Ptr;
-- Creates a pattern eelement that represents a concatenation of the
-- Creates a pattern element that represents a concatenation of the
-- two given pattern elements (i.e. the pattern L followed by R).
-- The result returned is always the same as L, but the pattern
-- referenced by L is modified to have R as a successor. This
@ -1304,7 +1304,7 @@ package body GNAT.Spitbol.Patterns is
Start : out Natural;
Stop : out Natural);
-- Identical in all respects to XMatch, except that trace information is
-- output on Standard_Ouput during execution of the match. This is the
-- output on Standard_Output during execution of the match. This is the
-- version that is called if the original Match call has Debug => True.
---------
@ -1590,7 +1590,7 @@ package body GNAT.Spitbol.Patterns is
return new PE'(PC_Alt, R.Index + 1, EOP, R);
-- If the left pattern is non-null, then build a reference vector
-- for its elements, and adjust their index values to acccomodate
-- for its elements, and adjust their index values to accommodate
-- the right hand elements. Then add the alternation node.
else
@ -3707,14 +3707,14 @@ package body GNAT.Spitbol.Patterns is
procedure Pop_Region;
pragma Inline (Pop_Region);
-- Used at the end of processing of an inner region. if the inner
-- Used at the end of processing of an inner region. If the inner
-- region left no stack entries, then all trace of it is removed.
-- Otherwise a PC_Restore_Region entry is pushed to ensure proper
-- handling of alternatives in the inner region.
procedure Push (Node : PE_Ptr);
pragma Inline (Push);
-- Make entry in pattern matching stack with current cursor valeu
-- Make entry in pattern matching stack with current cursor value
procedure Push_Region;
pragma Inline (Push_Region);
@ -5022,14 +5022,14 @@ package body GNAT.Spitbol.Patterns is
procedure Pop_Region;
pragma Inline (Pop_Region);
-- Used at the end of processing of an inner region. if the inner
-- Used at the end of processing of an inner region. If the inner
-- region left no stack entries, then all trace of it is removed.
-- Otherwise a PC_Restore_Region entry is pushed to ensure proper
-- handling of alternatives in the inner region.
procedure Push (Node : PE_Ptr);
pragma Inline (Push);
-- Make entry in pattern matching stack with current cursor valeu
-- Make entry in pattern matching stack with current cursor value
procedure Push_Region;
pragma Inline (Push_Region);

View File

@ -41,7 +41,7 @@
-- Summary of Pattern Matching Packages in GNAT Hierarchy --
------------------------------------------------------------
-- There are three related packages that perform pattern maching functions.
-- There are three related packages that perform pattern matching functions.
-- the following is an outline of these packages, to help you determine
-- which is best for your needs.
@ -154,7 +154,7 @@ package GNAT.Spitbol.Patterns is
-- ("ABC" or "AB") & ("DEF" or "CDE") & ("GH" or "IJ")
-- would succeed, afer two anchor point moves:
-- would succeed, after two anchor point moves:
-- "ABABCDEIJKL"
-- ^^^^^^^
@ -226,7 +226,7 @@ package GNAT.Spitbol.Patterns is
-- of the pattern, starting with zero occurrences. It is
-- thus equivalent to ("" or (P & ("" or (P & ("" ....)))).
-- The pattern P may contain any number of pattern elements
-- including the use of alternatiion and concatenation.
-- including the use of alternation and concatenation.
-- Break(S) Where S is a string, matches a string of zero or more
-- characters up to but not including a break character
@ -237,7 +237,7 @@ package GNAT.Spitbol.Patterns is
-- BreakX(S) Where S is a string, behaves exactly like Break(S) when
-- it first matches, but if a string is successfully matched,
-- then a susequent failure causes an attempt to extend the
-- then a subsequent failure causes an attempt to extend the
-- matched string.
-- Fence(P) Where P is a pattern, attempts to match the pattern P
@ -247,7 +247,7 @@ package GNAT.Spitbol.Patterns is
-- match proceeds, but on a subsequent failure, no attempt
-- is made to search for alternative matches of P. The
-- pattern P may contain any number of pattern elements
-- including the use of alternatiion and concatenation.
-- including the use of alternation and concatenation.
-- Len(N) Where N is a natural number, matches the given number of
-- characters. For example, Len(10) matches any string that
@ -255,7 +255,7 @@ package GNAT.Spitbol.Patterns is
-- NotAny(S) Where S is a string, matches a single character that is
-- not one of the characters of S. Fails if the current
-- characer is one of the given set of characters.
-- character is one of the given set of characters.
-- NSpan(S) Where S is a string, matches a string of zero or more
-- characters that is among the characters given in the
@ -690,7 +690,7 @@ package GNAT.Spitbol.Patterns is
-- if the language allowed, we would use in out parameters, but we are
-- not allowed to have in out parameters for functions. Instead we pass
-- actuals which must be variables, and with a bit of trickery in the
-- body, manage to interprete them properly as though they were indeed
-- body, manage to interpret them properly as though they were indeed
-- in out parameters.
pragma Warnings (Off, VString_Var);
@ -832,7 +832,7 @@ package GNAT.Spitbol.Patterns is
-- causes the entire match to be aborted if a subsequent failure occurs.
function Fence (P : Pattern) return Pattern;
-- Constructs a pattern that first matches P. if P fails, then the
-- Constructs a pattern that first matches P. If P fails, then the
-- constructed pattern fails. If P succeeds, then the match proceeds,
-- but if subsequent failure occurs, alternatives in P are not sought.
-- The idea of Fence is that each time the pattern is matched, just
@ -1054,7 +1054,7 @@ package GNAT.Spitbol.Patterns is
-- if the language allowed, we would use an in out parameter, but we are
-- not allowed to have in out parameters for functions. Instead we pass
-- actuals which must be variables, and with a bit of trickery in the
-- body, manage to interprete them properly as though they were indeed
-- body, manage to interpret them properly as though they were indeed
-- in out parameters.
function Match
@ -1142,8 +1142,8 @@ package GNAT.Spitbol.Patterns is
private
type PE;
-- Pattern element, a pattern is a plex structure of PE's. This type
-- is defined and sdescribed in the body of this package.
-- Pattern element, a pattern is a complex structure of PE's. This type
-- is defined and described in the body of this package.
type PE_Ptr is access all PE;
-- Pattern reference. PE's use PE_Ptr values to reference other PE's

View File

@ -33,6 +33,6 @@
-- This package does not require a body, since it is a package renaming. We
-- provide a dummy file containing a No_Body pragma so that previous versions
-- of the body (which did exist) will not intefere.
-- of the body (which did exist) will not interfere.
pragma No_Body;

View File

@ -162,7 +162,7 @@ package body Signalling_Fds is
R_Sock := Failure;
end loop;
-- Since the call to connect(2) has suceeded and the backlog limit on
-- Since the call to connect(2) has succeeded and the backlog limit on
-- the listening socket is 1, we know that there is now exactly one
-- pending connection on L_Sock, which is the one from R_Sock.