diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog index f659d3303eac87b56235b9eb91d000bdb560f276..67060228c28684c707e98de5da5bbe8a4391828d 100644 --- a/gcc/ada/ChangeLog +++ b/gcc/ada/ChangeLog @@ -1,3 +1,31 @@ +2008-04-10 Ralf Wildenhues <Ralf.Wildenhues@gmx.de> + + * gnat_ugn.texi: Fix typos. + * raise-gcc.c, repinfo.adb, repinfo.ads, restrict.adb, + restrict.ads, rtsfind.adb, rtsfind.ads, s-arit64.ads, + s-asthan-vms-alpha.adb, s-auxdec.ads, s-casuti.ads, + s-fatflt.ads, s-fatgen.adb, s-fatlfl.ads, + s-fatllf.ads, s-fatsfl.ads, s-filofl.ads, + s-finimp.adb, s-finroo.ads, s-fishfl.ads, + s-fvadfl.ads, s-fvaffl.ads, s-fvagfl.ads, + s-hibaen.ads, s-htable.ads, s-imgcha.adb, + s-imgenu.ads, s-imgint.adb, s-imgrea.adb, + s-inmaop-dummy.adb, s-inmaop.ads, s-interr-vms.adb, + s-interr-vxworks.adb, s-interr.adb, s-interr.ads, + s-intman-vxworks.ads, s-intman.ads, s-mastop-irix.adb, + s-os_lib.adb, s-os_lib.ads, s-osinte-aix.ads, + s-osinte-darwin.ads, s-osinte-freebsd.ads, + s-osinte-hpux.ads, s-osinte-lynxos-3.adb, + s-osinte-lynxos-3.ads, s-osinte-lynxos.ads, + s-osinte-rtems.ads, s-osinte-solaris-posix.ads, + s-osprim-mingw.adb, s-osprim-vms.adb, s-parame-ae653.ads, + s-parame-hpux.ads, s-parame-vms-alpha.ads, + s-parame-vms-ia64.ads, s-parame-vms-restrict.ads, + s-parame-vxworks.ads, s-parame.ads, s-parint.adb, + s-parint.ads, s-poosiz.adb, s-proinf-irix-athread.ads, + s-proinf.ads, s-regexp.adb, s-regpat.adb, s-regpat.ads, + s-rident.ads: Fix comment typos. + 2008-04-09 Samuel Tardieu <sam@rfc1149.net> PR ada/28305 diff --git a/gcc/ada/gnat_ugn.texi b/gcc/ada/gnat_ugn.texi index 799d720b535b7db51cb4acf72ceacd06aec2b23c..6654f5d16fe9ff4bdbfc4d1bf632e2beecb64156 100644 --- a/gcc/ada/gnat_ugn.texi +++ b/gcc/ada/gnat_ugn.texi @@ -22352,10 +22352,10 @@ same location as the @file{.gcno} files. The following executions will update those files, so that a cumulative result of the covered portions of the program is generated. -Finaly, you need to call the @code{gcov} tool. The different options of +Finally, you need to call the @code{gcov} tool. The different options of @code{gcov} are available in the GCC User's Guide, section 'Invoking gcov'. -This will create anotated source files with a @file{.gcov} extension: +This will create annotated source files with a @file{.gcov} extension: @file{my_main.adb} file will be analysed in @file{my_main.adb.gcov}. @node Gnat specifics @@ -22390,7 +22390,7 @@ most often, and are therefore the most time-consuming. @code{gprof} is the standard GNU profiling tool; it has been enhanced to better handle Ada programs and multitasking. -It is currently supported on the following platoforms +It is currently supported on the following platforms @itemize @bullet @item linux x86/x86_64 diff --git a/gcc/ada/raise-gcc.c b/gcc/ada/raise-gcc.c index 8a7cf5a568f5b3acba113ccca77505eaba6c7e49..bb25ea631d1722cb01139eb08337988d916b3252 100644 --- a/gcc/ada/raise-gcc.c +++ b/gcc/ada/raise-gcc.c @@ -362,7 +362,7 @@ db_phases (int phases) context stack and not the actual call chain. The ACTION and TTYPES tables remain unchanged, which allows to search them - during the propagation phase to determine wether or not the propagated + during the propagation phase to determine whether or not the propagated exception is handled somewhere. When it is, we only "jump" up once directly to the context where the handler will be found. Besides, this allows "break exception unhandled" to work also @@ -811,7 +811,7 @@ get_call_site_action_for (_Unwind_Context *uw_context, /* With CHOICE an exception choice representing an "exception - when" argument, and PROPAGATED_EXCEPTION a pointer to the currently propagated - occurrence, return true iif the latter matches the former, that is, if + occurrence, return true if the latter matches the former, that is, if PROPAGATED_EXCEPTION is caught by the handling code controlled by CHOICE. This takes care of the special Non_Ada_Error case on VMS. */ @@ -1135,7 +1135,7 @@ PERSONALITY_FUNCTION (version_arg_t version_arg, /* If we are going to install a cleanup context, decrement the cleanup count. This is required in a FORCED_UNWINDing phase (for an unhandled exception), as this is used from the forced unwinding handler in - Ada.Exceptions.Exception_Propagation to decide wether unwinding should + Ada.Exceptions.Exception_Propagation to decide whether unwinding should proceed further or Unhandled_Exception_Terminate should be called. */ if (action.kind == cleanup) Adjust_N_Cleanups_For (gnat_exception, -1); diff --git a/gcc/ada/repinfo.adb b/gcc/ada/repinfo.adb index a36fb5902e61e7b82dfe2fd4fa0d2de277c8c0f8..6764994e4f338a3a18a5f7f396117fcbcb67ef52 100644 --- a/gcc/ada/repinfo.adb +++ b/gcc/ada/repinfo.adb @@ -1095,7 +1095,7 @@ package body Repinfo is -- Bit_And_Expr, for which there is no direct support in uintp. Uint -- values out of the Int range are expected to be seen in such -- expressions only with overflowing byte sizes around, introducing - -- inherent unreliabilties in computations anyway. + -- inherent unreliabilities in computations anyway. ------- -- B -- diff --git a/gcc/ada/repinfo.ads b/gcc/ada/repinfo.ads index beaaf98eb5d59e182f1e4a2887337feaf30bb07b..39d037a15d9c2c3af3e8a8d7ad99ba6e25539976 100644 --- a/gcc/ada/repinfo.ads +++ b/gcc/ada/repinfo.ads @@ -88,7 +88,7 @@ package Repinfo is -- which contains the Size (more accurately the Object_SIze) value -- for the type or subtype. - -- For E_Component and E_Distriminant entities, the Esize (size + -- For E_Component and E_Discriminant entities, the Esize (size -- of component) and Component_Bit_Offset fields. Note that gigi -- does not (yet ???) back annotate Normalized_Position/First_Bit. @@ -156,12 +156,12 @@ package Repinfo is Truth_Or_Expr : constant TCode := 19; -- Boolean or 2 Truth_Xor_Expr : constant TCode := 20; -- Boolean xor 2 Truth_Not_Expr : constant TCode := 21; -- Boolean not 1 - Lt_Expr : constant TCode := 22; -- comparision < 2 - Le_Expr : constant TCode := 23; -- comparision <= 2 - Gt_Expr : constant TCode := 24; -- comparision > 2 - Ge_Expr : constant TCode := 25; -- comparision >= 2 - Eq_Expr : constant TCode := 26; -- comparision = 2 - Ne_Expr : constant TCode := 27; -- comparision /= 2 + Lt_Expr : constant TCode := 22; -- comparison < 2 + Le_Expr : constant TCode := 23; -- comparison <= 2 + Gt_Expr : constant TCode := 24; -- comparison > 2 + Ge_Expr : constant TCode := 25; -- comparison >= 2 + Eq_Expr : constant TCode := 26; -- comparison = 2 + Ne_Expr : constant TCode := 27; -- comparison /= 2 Bit_And_Expr : constant TCode := 28; -- Binary and 2 -- The following entry is used to represent a discriminant value in @@ -188,7 +188,7 @@ package Repinfo is -- => Discrim_Val, Op1 => discriminant_number). function Create_Discrim_Ref (Discr : Entity_Id) return Node_Ref; - -- Creates a refrerence to the discriminant whose entity is Discr + -- Creates a reference to the discriminant whose entity is Discr -------------------------------------------------------- -- Front-End Interface for Dynamic Size/Offset Values -- @@ -223,7 +223,7 @@ package Repinfo is -- In the case of components, if the location of the component is static, -- then all four fields (Component_Bit_Offset, Normalized_Position, Esize, - -- and Normalized_First_Bit) are set to appropraite values. In the case of + -- and Normalized_First_Bit) are set to appropriate values. In the case of -- a non-static component location, Component_Bit_Offset is not used and -- is left set to Unknown. Normalized_Position and Normalized_First_Bit -- are set appropriately. @@ -258,7 +258,7 @@ package Repinfo is -- Create_Dynamic_SO_Ref. The approach is that the front end makes -- the necessary Create_Dynamic_SO_Ref calls to associate the node -- and entity id values and the back end makes Get_Dynamic_SO_Ref - -- calls to retrive them. + -- calls to retrieve them. -------------------- -- ASIS_Interface -- diff --git a/gcc/ada/restrict.adb b/gcc/ada/restrict.adb index 068d601c2c6d959d0da5c43c8813fcf2cd5933ff..5049c5b1be49fac7bc3071d94d39d0bd1473722b 100644 --- a/gcc/ada/restrict.adb +++ b/gcc/ada/restrict.adb @@ -172,9 +172,9 @@ package body Restrict is end if; end loop; - -- If not predefied unit, then one special check still remains. - -- GNAT.Current_Exception is not allowed if we have restriction - -- No_Exception_Propagation active. + -- If not predefined unit, then one special check still + -- remains. GNAT.Current_Exception is not allowed if we have + -- restriction No_Exception_Propagation active. else if Name_Buffer (1 .. 8) = "g-curexc" then diff --git a/gcc/ada/restrict.ads b/gcc/ada/restrict.ads index 0cd4dbf28bf184184e0f26a63d90728038961f58..9dacefb300565f368a7f06b0ed71884a876c66c7 100644 --- a/gcc/ada/restrict.ads +++ b/gcc/ada/restrict.ads @@ -37,7 +37,7 @@ package Restrict is -- This variable records restrictions found in any units in the main -- extended unit, and in the case of restrictions checked for partition -- consistency, restrictions found in any with'ed units, parent specs - -- etc, since we may as well check as much as we can at compile time. + -- etc., since we may as well check as much as we can at compile time. -- These variables should not be referenced directly by clients. Instead -- use Check_Restrictions to record a violation of a restriction, and -- Restriction_Active to test if a given restriction is active. @@ -270,7 +270,7 @@ package Restrict is function Restricted_Profile return Boolean; -- Tests if set of restrictions corresponding to Profile (Restricted) is -- currently in effect (set by pragma Profile, or by an appropriate set - -- of individual Restrictions pragms). Returns True only if all the + -- of individual Restrictions pragmas). Returns True only if all the -- required restrictions are set. procedure Set_Profile_Restrictions diff --git a/gcc/ada/rtsfind.adb b/gcc/ada/rtsfind.adb index aceb6a11e111aa822e2541ac272969d916f5aca2..650e2eaad3f0dbd8799bc5bbe6edbbfffbc85213 100644 --- a/gcc/ada/rtsfind.adb +++ b/gcc/ada/rtsfind.adb @@ -100,9 +100,9 @@ package body Rtsfind is -- for the same entity can be satisfied immediately. -- NOTE: In order to avoid conflicts between record components and subprgs - -- that have the same name (ie. subprogram External_Tag and component - -- External_Tag of package Ada.Tags) this table is not used with - -- Record_Components. + -- that have the same name (i.e. subprogram External_Tag and + -- component External_Tag of package Ada.Tags) this table is not used + -- with Record_Components. RE_Table : array (RE_Id) of Entity_Id; @@ -145,7 +145,7 @@ package body Rtsfind is -- value in RTU_Id. procedure Load_Fail (S : String; U_Id : RTU_Id; Id : RE_Id); - -- Internal procedure called if we can't sucessfully locate or process a + -- Internal procedure called if we can't successfully locate or process a -- run-time unit. The parameters give information about the error message -- to be given. S is a reason for failing to compile the file and U_Id is -- the unit id. RE_Id is the RE_Id originally passed to RTE. The message in @@ -1214,7 +1214,7 @@ package body Rtsfind is -- If we didn't find the entity we want, something is wrong. The -- appropriate action will be taken by Check_CRT when we exit. - -- Cenerate a with-clause if the current unit is part of the extended + -- Generate a with-clause if the current unit is part of the extended -- main code unit, and if we have not already added the with. The clause -- is added to the appropriate unit (the current one). We do not need to -- generate it for a call issued from RTE_Component_Available. diff --git a/gcc/ada/rtsfind.ads b/gcc/ada/rtsfind.ads index 86779cb28d2ca6977169830b197045215ef26d49..ef61b8fd0e51d911884968bfee45b28556139634 100644 --- a/gcc/ada/rtsfind.ads +++ b/gcc/ada/rtsfind.ads @@ -501,7 +501,7 @@ package Rtsfind is RE_Detach_Handler, -- Ada.Interrupts RE_Reference, -- Ada.Interrupts - RE_Names, -- Ada.Interupts.Names + RE_Names, -- Ada.Interrupts.Names RE_Root_Stream_Type, -- Ada.Streams RE_Stream_Element, -- Ada.Streams @@ -2788,7 +2788,7 @@ package Rtsfind is -- run-time library, but allows only a subset of entities to be -- accessed. If any other entity is accessed, then it is treated -- as a configurable run-time violation, and the exception - -- RE_Not_Availble is raised. + -- RE_Not_Available is raised. -- The following array defines the set of units that contain entities -- that can be referenced in No_Run_Time mode. For each of these units, diff --git a/gcc/ada/s-arit64.ads b/gcc/ada/s-arit64.ads index 9364277f93877f8d9c8d89037e279e54cb8ce1d7..b414949b12726613051653aa6cf2219aca61937f 100644 --- a/gcc/ada/s-arit64.ads +++ b/gcc/ada/s-arit64.ads @@ -63,7 +63,7 @@ package System.Arith_64 is -- or if the quotient does not fit in 64-bits. Round indicates if -- the result should be rounded. If Round is False, then Q, R are -- the normal quotient and remainder from a truncating division. - -- If Round is True, then Q is the rounded quotient. the remainder + -- If Round is True, then Q is the rounded quotient. The remainder -- R is not affected by the setting of the Round flag. procedure Double_Divide diff --git a/gcc/ada/s-asthan-vms-alpha.adb b/gcc/ada/s-asthan-vms-alpha.adb index 16e627d43e94a529e32cf5623f86a4201bc227a6..9775f54bcd4ad2ca5ffa7f9052363b1da0d1dbde 100644 --- a/gcc/ada/s-asthan-vms-alpha.adb +++ b/gcc/ada/s-asthan-vms-alpha.adb @@ -149,7 +149,7 @@ package body System.AST_Handling is -- Note: When we say it works fine, there is one delicate point, which -- is that the code for the AST procedure itself requires the original - -- descriptor address. We handle this by saving the orignal descriptor + -- descriptor address. We handle this by saving the original descriptor -- address in this structure and restoring in Process_AST. type AST_Handler_Data is record @@ -237,7 +237,7 @@ package body System.AST_Handling is -- number of AST instances that can be stored in the buffer. Since -- these entries are immediately serviced by the high priority server -- task that does the actual entry queuing, it is very unusual to have - -- any significant number of entries simulaneously queued. + -- any significant number of entries simultaneously queued. AST_Service_Queue : array (AST_Service_Queue_Index) of AST_Instance; pragma Volatile_Components (AST_Service_Queue); diff --git a/gcc/ada/s-auxdec.ads b/gcc/ada/s-auxdec.ads index e43efeed04f7af07a4692616ff7ad0cece3f72ea..c507a7e7546c4921a6714903457974aed50a1952 100644 --- a/gcc/ada/s-auxdec.ads +++ b/gcc/ada/s-auxdec.ads @@ -48,7 +48,7 @@ package System.Aux_DEC is -- name Short_Address is used for the short address form. To avoid -- difficulties (in regression tests and elsewhere) with units that -- reference Short_Address, it is provided for other targets as a - -- synonum for the normal Address type, and, as in the case where + -- synonym for the normal Address type, and, as in the case where -- the lengths are different, Address and Short_Address can be -- freely inter-converted. diff --git a/gcc/ada/s-casuti.ads b/gcc/ada/s-casuti.ads index 8ba633c288ce00c2a12a6bc9404ee68f4f4ef87a..6831942d3fb1d693f66d7f3de45bd7c5af9d69ab 100644 --- a/gcc/ada/s-casuti.ads +++ b/gcc/ada/s-casuti.ads @@ -53,7 +53,7 @@ package System.Case_Util is -- returns the input argument unchanged. procedure To_Upper (A : in out String); - -- 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; -- Converts A to lower case if it is an upper case letter, otherwise diff --git a/gcc/ada/s-fatflt.ads b/gcc/ada/s-fatflt.ads index 2ba596bc4a5fd77444a55c52ded8bc0385182c87..a12907919488af52889fe7e97cec40862078834c 100644 --- a/gcc/ada/s-fatflt.ads +++ b/gcc/ada/s-fatflt.ads @@ -39,7 +39,7 @@ with System.Fat_Gen; package System.Fat_Flt is pragma Pure; - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-fatgen.adb b/gcc/ada/s-fatgen.adb index 20f3ead28282202c744f78b4243bdaa35a9d6d31..f690177a59fd8438ac3bf25722ac91a6fa5560a9 100644 --- a/gcc/ada/s-fatgen.adb +++ b/gcc/ada/s-fatgen.adb @@ -54,7 +54,7 @@ package body System.Fat_Gen is Invrad : constant T := 1.0 / Rad; subtype Expbits is Integer range 0 .. 6; - -- 2 ** (2 ** 7) might overflow. how big can radix-16 exponents get? + -- 2 ** (2 ** 7) might overflow. How big can radix-16 exponents get? Log_Power : constant array (Expbits) of Integer := (1, 2, 4, 8, 16, 32, 64); @@ -569,7 +569,7 @@ package body System.Fat_Gen is return X; end if; - -- Nonzero x. essentially, just multiply repeatedly by Rad ** (+-2**n) + -- Nonzero x essentially, just multiply repeatedly by Rad ** (+-2**n) declare Y : T := X; @@ -660,7 +660,7 @@ package body System.Fat_Gen is -- since the exponent is going to be reduced. -- Note that X_Frac has the same sign as X, so if X_Frac is -0.5, - -- then we know that we have a ngeative number (and hence a + -- then we know that we have a negative number (and hence a -- negative power of 2). if X_Frac = -0.5 then @@ -809,14 +809,14 @@ package body System.Fat_Gen is -- entire floating-point value. Do not take into account excessive -- padding, as occurs on IA-64 where 80 bits floats get padded to 128 -- bits. In general, the exponent field cannot be larger than 15 bits, - -- even for 128-bit floating-poin t types, so the final format size + -- even for 128-bit floating-point types, so the final format size -- won't be larger than T'Mantissa + 16. type Float_Rep is array (Rep_Index range 0 .. Rep_Index (Rep_Words - 1)) of Float_Word; pragma Suppress_Initialization (Float_Rep); - -- This pragma supresses the generation of an initialization procedure + -- This pragma suppresses the generation of an initialization procedure -- for type Float_Rep when operating in Initialize/Normalize_Scalars -- mode. This is not just a matter of efficiency, but of functionality, -- since Valid has a pragma Inline_Always, which is not permitted if @@ -873,8 +873,8 @@ package body System.Fat_Gen is begin if T'Denorm then - -- All denormalized numbers are valid, so only invalid numbers are - -- overflows and NaN's, both with exponent = Emax + 1. + -- All denormalized numbers are valid, so the only invalid numbers + -- are overflows and NaNs, both with exponent = Emax + 1. return E /= IEEE_Emax + 1; diff --git a/gcc/ada/s-fatlfl.ads b/gcc/ada/s-fatlfl.ads index 844f1b4739ad26d54d7e13d2bcd94d5168d00050..b4c5c510af84a7781613c03b076838df4e440473 100644 --- a/gcc/ada/s-fatlfl.ads +++ b/gcc/ada/s-fatlfl.ads @@ -39,7 +39,7 @@ with System.Fat_Gen; package System.Fat_LFlt is pragma Pure; - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-fatllf.ads b/gcc/ada/s-fatllf.ads index f2d554c4dab3f7b83344c20cffe4bdc4bc2cc425..6869d8e7e85e76b8e48fbc2935216a58265fd63f 100644 --- a/gcc/ada/s-fatllf.ads +++ b/gcc/ada/s-fatllf.ads @@ -39,7 +39,7 @@ with System.Fat_Gen; package System.Fat_LLF is pragma Pure; - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-fatsfl.ads b/gcc/ada/s-fatsfl.ads index 129efea64a2c3f72140784293232996de625fc9e..8539723bf0438660d4725c32b118a19a7a09e977 100644 --- a/gcc/ada/s-fatsfl.ads +++ b/gcc/ada/s-fatsfl.ads @@ -39,7 +39,7 @@ with System.Fat_Gen; package System.Fat_SFlt is pragma Pure; - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-filofl.ads b/gcc/ada/s-filofl.ads index dded3cf5a940778e75221997dfba8b12f7132c1b..b185890bf1ed3cca760ac4ac1ada8fd06c592237 100644 --- a/gcc/ada/s-filofl.ads +++ b/gcc/ada/s-filofl.ads @@ -32,7 +32,7 @@ ------------------------------------------------------------------------------ -- This package contains an instantiation of the floating-point attribute --- runtime routines for IEEE long float. This is used on VMS targest where +-- runtime routines for IEEE long float. This is used on VMS targets where -- we can't just use Long_Float, since this may have been mapped to Vax_Float -- using a Float_Representation configuration pragma. @@ -44,7 +44,7 @@ package System.Fat_IEEE_Long_Float is type Fat_IEEE_Long is digits 15; pragma Float_Representation (IEEE_Float, Fat_IEEE_Long); - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-finimp.adb b/gcc/ada/s-finimp.adb index 4ed7c6ce1e889870758f0796e956144c35ce53ee..2d6defb3e6b1b6eca9674b0433b56a878b97d4e7 100644 --- a/gcc/ada/s-finimp.adb +++ b/gcc/ada/s-finimp.adb @@ -100,7 +100,7 @@ package body System.Finalization_Implementation is -- Subtract the offset to the pointer procedure Reverse_Adjust (P : Finalizable_Ptr); - -- Ajust the components in the reverse order in which they are stored + -- Adjust the components in the reverse order in which they are stored -- on the finalization list. (Adjust and Finalization are not done in -- the same order) @@ -139,7 +139,7 @@ package body System.Finalization_Implementation is First_Comp := Object.F; Object.F := null; -- nothing adjusted yet. - Ptr_Adjust (First_Comp); -- set addresss of first component. + Ptr_Adjust (First_Comp); -- set address of first component. Reverse_Adjust (First_Comp); -- Then Adjust the controller itself @@ -412,7 +412,7 @@ package body System.Finalization_Implementation is -- At this stage, we know that the controller is part of the -- ancestor corresponding to the tag "The_Tag" and that its parent -- is variable sized. We assume that the _controller is the first - -- compoment right after the parent. + -- component right after the parent. -- ??? note that it may not be true if there are new discriminants diff --git a/gcc/ada/s-finroo.ads b/gcc/ada/s-finroo.ads index 79f403c5fc6bb5b5726c9e1bb0e51aaa621813fb..0f4b7d189bf393c4973ef3faa6b2bfb58def9466 100644 --- a/gcc/ada/s-finroo.ads +++ b/gcc/ada/s-finroo.ads @@ -61,7 +61,7 @@ package System.Finalization_Root is procedure Finalize (Object : in out Root_Controlled); procedure Adjust (Object : in out Root_Controlled); - -- Stream-oriented attibutes for Root_Controlled. These must be empty so + -- Stream-oriented attributes for Root_Controlled. These must be empty so -- as to not copy the finalization chain pointers. They are declared in -- a nested package so that they do not create primitive operations of -- Root_Controlled. Otherwise this would add unwanted primitives to (the diff --git a/gcc/ada/s-fishfl.ads b/gcc/ada/s-fishfl.ads index 7308618f1ad9189d4e6edd4eac5e8acbb7398a1d..0b0839fc998cb22d3a6423df1002c43f246403ae 100644 --- a/gcc/ada/s-fishfl.ads +++ b/gcc/ada/s-fishfl.ads @@ -32,7 +32,7 @@ ------------------------------------------------------------------------------ -- This package contains an instantiation of the floating-point attribute --- runtime routines for IEEE short float. This is used on VMS targest where +-- runtime routines for IEEE short float. This is used on VMS targets where -- we can't just use Float, since this may have been mapped to Vax_Float -- using a Float_Representation configuration pragma. @@ -44,7 +44,7 @@ package System.Fat_IEEE_Short_Float is type Fat_IEEE_Short is digits 6; pragma Float_Representation (IEEE_Float, Fat_IEEE_Short); - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-fvadfl.ads b/gcc/ada/s-fvadfl.ads index 05a367ca42f1af720ccb71d69db2441bddc41537..76c3a0b47363ba2e3326149a9340cfcf0d58f733 100644 --- a/gcc/ada/s-fvadfl.ads +++ b/gcc/ada/s-fvadfl.ads @@ -41,12 +41,12 @@ package System.Fat_VAX_D_Float is pragma Warnings (Off); -- This unit is normally used only for VMS, but we compile it for other - -- targest for the convenience of testing vms code using -gnatdm. + -- targets for the convenience of testing vms code using -gnatdm. type Fat_VAX_D is digits 9; pragma Float_Representation (VAX_Float, Fat_VAX_D); - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-fvaffl.ads b/gcc/ada/s-fvaffl.ads index 0c769bfd9d1cefdc9ddaf6be6cf5d18dbdf6e90e..729391cb5df26712369c10152b299c5892b140a7 100644 --- a/gcc/ada/s-fvaffl.ads +++ b/gcc/ada/s-fvaffl.ads @@ -41,12 +41,12 @@ package System.Fat_VAX_F_Float is pragma Warnings (Off); -- This unit is normally used only for VMS, but we compile it for other - -- targest for the convenience of testing vms code using -gnatdm. + -- targets for the convenience of testing vms code using -gnatdm. type Fat_VAX_F is digits 6; pragma Float_Representation (VAX_Float, Fat_VAX_F); - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-fvagfl.ads b/gcc/ada/s-fvagfl.ads index 50a06b9e9e1fe53649db06dbd8f439964095d07e..bbce6ef973193c77cde86a65bf3d49ffef2e0242 100644 --- a/gcc/ada/s-fvagfl.ads +++ b/gcc/ada/s-fvagfl.ads @@ -41,12 +41,12 @@ package System.Fat_VAX_G_Float is pragma Warnings (Off); -- This unit is normally used only for VMS, but we compile it for other - -- targest for the convenience of testing vms code using -gnatdm. + -- targets for the convenience of testing vms code using -gnatdm. type Fat_VAX_G is digits 15; pragma Float_Representation (VAX_Float, Fat_VAX_G); - -- Note the only entity from this package that is acccessed by Rtsfind + -- Note the only entity from this package that is accessed by Rtsfind -- is the name of the package instantiation. Entities within this package -- (i.e. the individual floating-point attribute routines) are accessed -- by name using selected notation. diff --git a/gcc/ada/s-hibaen.ads b/gcc/ada/s-hibaen.ads index 90ba0155d34b806c4be7f5b2ff03973852d11043..d7ae2325106f657614ae8da59994f4b1b0ed3fe9 100644 --- a/gcc/ada/s-hibaen.ads +++ b/gcc/ada/s-hibaen.ads @@ -73,7 +73,7 @@ package System.HIE_Back_End is -- This entity controls whether the front end allows generation of -- long shift instructions, i.e. shifts that operate on 64-bit values. -- Such shifts are required for the implementation of fixed-point - -- types longer than 32 bits. This can safetly be set as High_Integrity + -- types longer than 32 bits. This can safely be set as High_Integrity -- on 64-bit machines that provide this operation at the hardware level, -- but on some 32-bit machines a run time call is required. If there -- is a certifiable version available of the relevant run-time routines, diff --git a/gcc/ada/s-htable.ads b/gcc/ada/s-htable.ads index d5116c69f3b38c963f7667bd704fa66026b6b4a2..d7bcbef5f38477c7820698466f49d63c0ee913bb 100644 --- a/gcc/ada/s-htable.ads +++ b/gcc/ada/s-htable.ads @@ -183,7 +183,7 @@ package System.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. diff --git a/gcc/ada/s-imgcha.adb b/gcc/ada/s-imgcha.adb index a8d7c10bc0943245a28a58b20cefc6658856b408..3d9bbe9b86b912b553eec5f8f504047740028667 100644 --- a/gcc/ada/s-imgcha.adb +++ b/gcc/ada/s-imgcha.adb @@ -159,7 +159,7 @@ package body System.Img_Char is end; end if; - -- Normal characters yield the character enlosed in quotes (RM 3.5(32)) + -- Normal characters yield the character enclosed in quotes (RM 3.5(32)) else S (1) := '''; diff --git a/gcc/ada/s-imgenu.ads b/gcc/ada/s-imgenu.ads index 2b6fbdd310948ca5fac5ce1d6013f8527cbb2e8e..9dc66e686348513a92c1d315bfdc61bb525c61d1 100644 --- a/gcc/ada/s-imgenu.ads +++ b/gcc/ada/s-imgenu.ads @@ -39,8 +39,8 @@ -- Note: this is an obsolete package, replaced by System.Img_Enum_New, which -- provides procedures instead of functions for these enumeration image calls. -- The reason we maintain this package is that when bootstrapping with old --- compilers, the old compiler will search for this unit, expectinng to find --- these functions. The new commpiler will search for procedures in the new +-- compilers, the old compiler will search for this unit, expecting to find +-- these functions. The new compiler will search for procedures in the new -- version of the unit. pragma Warnings (Off); diff --git a/gcc/ada/s-imgint.adb b/gcc/ada/s-imgint.adb index 74a5b736e48fc77924a6c44556994200810a3f99..a6c31489e69f0e1beaf5ec97a1c36829e96adfed 100644 --- a/gcc/ada/s-imgint.adb +++ b/gcc/ada/s-imgint.adb @@ -65,7 +65,7 @@ package body System.Img_Int is end if; end Set_Digits; - -- Start of processinng for Image_Integer + -- Start of processing for Image_Integer begin P := 1; diff --git a/gcc/ada/s-imgrea.adb b/gcc/ada/s-imgrea.adb index e9fd56067f87dd38e7fe27784f5bad4fa15fc966..bbcf225a1dd4c02657ed21f06c7accb1e437ac58 100644 --- a/gcc/ada/s-imgrea.adb +++ b/gcc/ada/s-imgrea.adb @@ -87,7 +87,7 @@ package body System.Img_Real is pragma Assert (S'First = 1); begin - -- Decide wether a blank should be prepended before the call to + -- Decide whether a blank should be prepended before the call to -- Set_Image_Real. We generate a blank for positive values, and -- also for positive zeroes. For negative zeroes, we generate a -- space only if Signed_Zeroes is True (the RM only permits the diff --git a/gcc/ada/s-inmaop-dummy.adb b/gcc/ada/s-inmaop-dummy.adb index edd636ed077d8f4313736c1f9b5b0d4656dbf9f1..4c7f77c63ae191900e420e43c704b61703e80a2b 100644 --- a/gcc/ada/s-inmaop-dummy.adb +++ b/gcc/ada/s-inmaop-dummy.adb @@ -134,9 +134,9 @@ package body System.Interrupt_Management.Operations is null; end Empty_Interrupt_Mask; - ----------------------- - -- Add_To_Sigal_Mask -- - ----------------------- + --------------------------- + -- Add_To_Interrupt_Mask -- + --------------------------- procedure Add_To_Interrupt_Mask (Mask : access Interrupt_Mask; diff --git a/gcc/ada/s-inmaop.ads b/gcc/ada/s-inmaop.ads index 1bd660ef8752bf803eeeb98444820bd4c4d514f8..2e9674d22df8e7213dc734fe0ed1d264f4c65c27 100644 --- a/gcc/ada/s-inmaop.ads +++ b/gcc/ada/s-inmaop.ads @@ -96,7 +96,7 @@ package System.Interrupt_Management.Operations is procedure Copy_Interrupt_Mask (X : out Interrupt_Mask; Y : Interrupt_Mask); pragma Inline (Copy_Interrupt_Mask); - -- Assigment needed for limited private type Interrupt_Mask + -- Assignment needed for limited private type Interrupt_Mask procedure Interrupt_Self_Process (Interrupt : Interrupt_ID); pragma Inline (Interrupt_Self_Process); diff --git a/gcc/ada/s-interr-vms.adb b/gcc/ada/s-interr-vms.adb index 2711e036cbedfc014dfbc234c180c3a469dfd30a..83e814160d418a5ffe5b42d42c6a38f152e81719 100644 --- a/gcc/ada/s-interr-vms.adb +++ b/gcc/ada/s-interr-vms.adb @@ -222,7 +222,7 @@ package body System.Interrupts is begin -- This routine registers the Handler as usable for Dynamic -- Interrupt Handler. Routines attaching and detaching Handler - -- dynamically should first consult if the Handler is rgistered. + -- dynamically should first consult if the Handler is registered. -- A Program Error should be raised if it is not registered. -- The pragma Interrupt_Handler can only appear in the library @@ -372,7 +372,7 @@ package body System.Interrupts is -- Calling this procedure with New_Handler = null and Static = True -- means we want to detach the current handler regardless of the - -- previous handler's binding status (ie. do not care if it is a + -- previous handler's binding status (i.e. do not care if it is a -- dynamic or static handler). -- This option is needed so that during the finalization of a PO, we @@ -398,7 +398,7 @@ package body System.Interrupts is -- Calling this procedure with New_Handler = null and Static = True means -- we want to detach the current handler regardless of the previous - -- handler's binding status (ie. do not care if it is dynamic or static + -- handler's binding status (i.e. do not care if it is dynamic or static -- handler). -- This option is needed so that during the finalization of a PO, we can @@ -630,7 +630,7 @@ package body System.Interrupts is "dynamic Handler"; end if; - -- The interrupt should no longer be ingnored if it was ever ignored + -- The interrupt should no longer be ignored if it was ever ignored Ignored (Interrupt) := False; @@ -715,7 +715,7 @@ package body System.Interrupts is System.Tasking.Utilities.Make_Independent; - -- Environmen task gets its own interrupt mask, saves it, + -- Environment task gets its own interrupt mask, saves it, -- and then masks all interrupts except the Keep_Unmasked set. -- During rendezvous, the Interrupt_Manager receives the old @@ -741,17 +741,17 @@ package body System.Interrupts is -- This sigwaiting is needed so that we make sure a Server_Task is -- out of its own sigwait state. This extra synchronization is - -- necessary to prevent following senarios. + -- necessary to prevent following scenarios. -- 1) Interrupt_Manager sends an Abort_Task_Interrupt to the -- Server_Task then changes its own interrupt mask (OS level). -- If an interrupt (corresponding to the Server_Task) arrives - -- in the nean time we have the Interrupt_Manager umnasked and + -- in the mean time we have the Interrupt_Manager unmasked and -- the Server_Task waiting on sigwait. -- 2) For unbinding handler, we install a default action in the -- Interrupt_Manager. POSIX.1c states that the result of using - -- "sigwait" and "sigaction" simaltaneously on the same interrupt + -- "sigwait" and "sigaction" simultaneously on the same interrupt -- is undefined. Therefore, we need to be informed from the -- Server_Task of the fact that the Server_Task is out of its -- sigwait stage. @@ -806,7 +806,7 @@ package body System.Interrupts is "A binding for this interrupt is already present"; end if; - -- The interrupt should no longer be ingnored if + -- The interrupt should no longer be ignored if -- it was ever ignored. Ignored (Interrupt) := False; @@ -938,7 +938,7 @@ package body System.Interrupts is -- (Abort_Task_Interrupt) from the Interrupt_Manager for unbinding -- a Procedure Handler or an Entry. Or it could be a wake up -- from status change (Unblocked -> Blocked). If that is not - -- the case, we should exceute the attached Procedure or Entry. + -- the case, we should execute the attached Procedure or Entry. if Single_Lock then POP.Lock_RTS; diff --git a/gcc/ada/s-interr-vxworks.adb b/gcc/ada/s-interr-vxworks.adb index fac4cfc8619ffd5b85c5fe0c23de41f5a9b5230e..98254e617be587548dae1870fe4485f9e39c15f9 100644 --- a/gcc/ada/s-interr-vxworks.adb +++ b/gcc/ada/s-interr-vxworks.adb @@ -232,7 +232,7 @@ package body System.Interrupts is -- Calling this procedure with New_Handler = null and Static = True -- means we want to detach the current handler regardless of the - -- previous handler's binding status (ie. do not care if it is a + -- previous handler's binding status (i.e. do not care if it is a -- dynamic or static handler). -- This option is needed so that during the finalization of a PO, we @@ -342,7 +342,7 @@ package body System.Interrupts is -- Calling this procedure with New_Handler = null and Static = True -- means we want to detach the current handler regardless of the - -- previous handler's binding status (ie. do not care if it is a + -- previous handler's binding status (i.e. do not care if it is a -- dynamic or static handler). -- This option is needed so that during the finalization of a PO, we @@ -616,7 +616,7 @@ package body System.Interrupts is -- Each Interrupt_Server_Task has an associated binary semaphore -- on which it pends once it's been started. This routine determines - -- The appropriate semaphore and and issues a semGive call, waking + -- The appropriate semaphore and issues a semGive call, waking -- the server task. When a handler is unbound, -- System.Interrupts.Unbind_Handler issues a semFlush, and the -- server task deletes its semaphore and terminates. diff --git a/gcc/ada/s-interr.adb b/gcc/ada/s-interr.adb index 3fe420303a6d225044ff2749b0d393d87edc8cd7..44411125493f2b362f1fb9a761e4c9b10fc43c44 100644 --- a/gcc/ada/s-interr.adb +++ b/gcc/ada/s-interr.adb @@ -44,7 +44,7 @@ -- Note : Direct calls to sigaction, sigprocmask, pthread_sigsetmask or any -- other low-level interface that changes the interrupt action or -- interrupt mask needs a careful thought. --- One may acheive the effect of system calls first masking RTS blocked +-- One may achieve the effect of system calls first masking RTS blocked -- (by calling Block_Interrupt) for the interrupt under consideration. -- This will make all the tasks in RTS blocked for the Interrupt. @@ -224,7 +224,7 @@ package body System.Interrupts is -- Calling this procedure with New_Handler = null and Static = True means -- we want to detach the current handler regardless of the previous - -- handler's binding status (ie. do not care if it is a dynamic or static + -- handler's binding status (i.e. do not care if it is a dynamic or static -- handler). -- This option is needed so that during the finalization of a PO, we can @@ -342,7 +342,7 @@ package body System.Interrupts is -- Calling this procedure with New_Handler = null and Static = True means -- we want to detach the current handler regardless of the previous - -- handler's binding status (ie. do not care if it is a dynamic or static + -- handler's binding status (i.e. do not care if it is a dynamic or static -- handler). -- This option is needed so that during the finalization of a PO, we can @@ -705,7 +705,7 @@ package body System.Interrupts is if not Blocked (Interrupt) then -- Mask this task for the given Interrupt so that all tasks - -- are masked for the Interrupt and the actuall delivery of the + -- are masked for the Interrupt and the actual delivery of the -- Interrupt will be caught using "sigwait" by the -- corresponding Server_Task. @@ -867,7 +867,7 @@ package body System.Interrupts is "dynamic Handler"; end if; - -- The interrupt should no longer be ingnored if + -- The interrupt should no longer be ignored if -- it was ever ignored. Ignored (Interrupt) := False; @@ -958,17 +958,17 @@ package body System.Interrupts is -- This sigwaiting is needed so that we make sure a Server_Task is -- out of its own sigwait state. This extra synchronization is - -- necessary to prevent following senarios. + -- necessary to prevent following scenarios. -- 1) Interrupt_Manager sends an Abort_Task_Interrupt to the -- Server_Task then changes its own interrupt mask (OS level). -- If an interrupt (corresponding to the Server_Task) arrives - -- in the nean time we have the Interrupt_Manager umnasked and + -- in the mean time we have the Interrupt_Manager unmasked and -- the Server_Task waiting on sigwait. -- 2) For unbinding handler, we install a default action in the -- Interrupt_Manager. POSIX.1c states that the result of using - -- "sigwait" and "sigaction" simaltaneously on the same interrupt + -- "sigwait" and "sigaction" simultaneously on the same interrupt -- is undefined. Therefore, we need to be informed from the -- Server_Task of the fact that the Server_Task is out of its -- sigwait stage. @@ -1029,7 +1029,7 @@ package body System.Interrupts is "A binding for this interrupt is already present"; end if; - -- The interrupt should no longer be ingnored if + -- The interrupt should no longer be ignored if -- it was ever ignored. Ignored (Interrupt) := False; @@ -1067,7 +1067,7 @@ package body System.Interrupts is if not Is_Reserved (J) then if User_Entry (J).T = T then - -- The interrupt should no longer be ingnored if + -- The interrupt should no longer be ignored if -- it was ever ignored. Ignored (J) := False; @@ -1301,7 +1301,7 @@ package body System.Interrupts is -- (Abort_Task_Interrupt) from the Interrupt_Manager for unbinding -- a Procedure Handler or an Entry. Or it could be a wake up -- from status change (Unblocked -> Blocked). If that is not - -- the case, we should exceute the attached Procedure or Entry. + -- the case, we should execute the attached Procedure or Entry. Self_ID.Common.State := Interrupt_Server_Blocked_On_Event_Flag; POP.Unlock (Self_ID); diff --git a/gcc/ada/s-interr.ads b/gcc/ada/s-interr.ads index 022d05471a3c76369e8b5b3eb056d953cd46efd5..4254b30c0cf83ebe03cecb553def58a4ee7e46da 100644 --- a/gcc/ada/s-interr.ads +++ b/gcc/ada/s-interr.ads @@ -150,7 +150,7 @@ package System.Interrupts is -- Comment needed ??? procedure Ignore_Interrupt (Interrupt : Interrupt_ID); - -- Set the sigacion for the interrupt to SIG_IGN + -- Set the sigaction for the interrupt to SIG_IGN procedure Unignore_Interrupt (Interrupt : Interrupt_ID); -- Comment needed ??? @@ -162,7 +162,7 @@ package System.Interrupts is -- other low-level interface that changes the signal action or signal mask -- needs a careful thought. - -- One may acheive the effect of system calls first making RTS blocked (by + -- One may achieve the effect of system calls first making RTS blocked (by -- calling Block_Interrupt) for the signal under consideration. This will -- make all the tasks in RTS blocked for the Interrupt. @@ -188,7 +188,7 @@ package System.Interrupts is -- (2) Attach_Handler pragmas are used, and possibly Interrupt_Handler -- pragma. We need to attach the handlers to the given interrupts when the - -- objet is elaborated. This should be done by constructing an array of + -- object is elaborated. This should be done by constructing an array of -- pairs (interrupt, handler) from the pragmas and calling Install_Handlers -- with it (types to be used are New_Handler_Item and New_Handler_Array). -- On finalization, we need to restore the handlers that were installed diff --git a/gcc/ada/s-intman-vxworks.ads b/gcc/ada/s-intman-vxworks.ads index b249301d723497bc31177c997207b25d52d1a522..03937811ec4c8cc5f159cc14915a779c46b613cc 100644 --- a/gcc/ada/s-intman-vxworks.ads +++ b/gcc/ada/s-intman-vxworks.ads @@ -45,7 +45,7 @@ -- Interrupt_ID is used to derive the type in Ada.Interrupts, and -- adding more operations to that type would be illegal according -- to the Ada Reference Manual. This is the reason why the signals --- sets are implemeneted using visible arrays rather than functions. +-- sets are implemented using visible arrays rather than functions. with System.OS_Interface; diff --git a/gcc/ada/s-intman.ads b/gcc/ada/s-intman.ads index ae68d27a334dd2a18bc9795dad34918497ba5fe3..fb91662bda121c3a74f042bb2b9cf23fa8ee5c05 100644 --- a/gcc/ada/s-intman.ads +++ b/gcc/ada/s-intman.ads @@ -42,7 +42,7 @@ -- Interrupt_ID into the visible part of this package. The type Interrupt_ID -- is used to derive the type in Ada.Interrupts, and adding more operations -- to that type would be illegal according to the Ada Reference Manual. This --- is the reason why the signals sets are implemeneted using visible arrays +-- is the reason why the signals sets are implemented using visible arrays -- rather than functions. with System.OS_Interface; diff --git a/gcc/ada/s-mastop-irix.adb b/gcc/ada/s-mastop-irix.adb index 2e3d513bc66112fe17df214159048e6acdd81546..a5b04e0811737e0ac43aee885f52f5150ed6a055 100644 --- a/gcc/ada/s-mastop-irix.adb +++ b/gcc/ada/s-mastop-irix.adb @@ -45,7 +45,7 @@ package body System.Machine_State_Operations is use System.Storage_Elements; - -- The exc_unwind function in libexc operats on a Sigcontext + -- The exc_unwind function in libexc operates on a Sigcontext -- Type sigcontext_t is defined in /usr/include/sys/signal.h. -- We define an equivalent Ada type here. From the comments in @@ -115,7 +115,7 @@ package body System.Machine_State_Operations is o32n : constant Natural := Boolean'Pos (o32); n32n : constant Natural := Boolean'Pos (n32); -- Flags to indicate which ABI is in effect for this compilation. For the - -- purposes of this unit, the n32 and n64 ABI's are identical. + -- purposes of this unit, the n32 and n64 ABIs are identical. LSC : constant Character := Character'Val (o32n * Character'Pos ('w') + n32n * Character'Pos ('d')); diff --git a/gcc/ada/s-os_lib.adb b/gcc/ada/s-os_lib.adb index 3c89fd38184d5a8ad89281e500e1370c16ce3802..ff65720d6e4c97904e00f1b138d60db6acbf4d18 100755 --- a/gcc/ada/s-os_lib.adb +++ b/gcc/ada/s-os_lib.adb @@ -293,7 +293,7 @@ package body System.OS_Lib is -- Internal exception raised to signal error in copy function Build_Path (Dir : String; File : String) return String; - -- Returns pathname Dir catenated with File adding the directory + -- Returns pathname Dir concatenated with File adding the directory -- separator only if needed. procedure Copy (From, To : File_Descriptor); @@ -1833,7 +1833,7 @@ package body System.OS_Lib is -- First, convert VMS file spec to Unix file spec. -- If Name is not in VMS syntax, then this is equivalent - -- to put Name at the begining of Path_Buffer. + -- to put Name at the beginning of Path_Buffer. VMS_Conversion : begin The_Name (1 .. Name'Length) := Name; diff --git a/gcc/ada/s-os_lib.ads b/gcc/ada/s-os_lib.ads index e3c1079df19b12e0b0a6cc447f89ea2bd4dfcdf0..8c319c845e1fc322cb435ae176cad666e68d6d90 100755 --- a/gcc/ada/s-os_lib.ads +++ b/gcc/ada/s-os_lib.ads @@ -65,7 +65,7 @@ package System.OS_Lib is ----------------------- -- These are reexported from package Strings (which was introduced to - -- avoid different packages declarting different types unnecessarily). + -- avoid different packages declaring different types unnecessarily). -- See package System.Strings for details. subtype String_Access is Strings.String_Access; @@ -875,7 +875,7 @@ private -- bootstrap path problems. To be changed later ??? Invalid_Time : constant OS_Time := -1; - -- This value should match the return valud by __gnat_file_time_* + -- This value should match the return value from __gnat_file_time_* pragma Inline ("<"); pragma Inline (">"); diff --git a/gcc/ada/s-osinte-aix.ads b/gcc/ada/s-osinte-aix.ads index 6985915869d8b4f906bb3d244fd01690b83ff0bc..b5de4f28ba9c04c7cdb56aa2125120e85c0308c5 100644 --- a/gcc/ada/s-osinte-aix.ads +++ b/gcc/ada/s-osinte-aix.ads @@ -132,7 +132,7 @@ package System.OS_Interface is SIGCPUFAIL : constant := 59; -- Predictive De-configuration of Processors SIGKAP : constant := 60; -- keep alive poll from native keyboard SIGGRANT : constant := SIGKAP; -- monitor mode granted - SIGRETRACT : constant := 61; -- monitor mode should be relinguished + SIGRETRACT : constant := 61; -- monitor mode should be relinquished SIGSOUND : constant := 62; -- sound control has completed SIGSAK : constant := 63; -- secure attention key @@ -311,7 +311,7 @@ package System.OS_Interface is -- No alternate signal stack is used on this platform Stack_Base_Available : constant Boolean := False; - -- Indicates wether the stack base is available on this target + -- Indicates whether the stack base is available on this target function Get_Stack_Base (thread : pthread_t) return Address; pragma Inline (Get_Stack_Base); diff --git a/gcc/ada/s-osinte-darwin.ads b/gcc/ada/s-osinte-darwin.ads index 8dd28dbd0e571ac2c2651771faaf9672fb501994..d53e2c43dcabb9ec575f356288c3d7dd7959c4bf 100644 --- a/gcc/ada/s-osinte-darwin.ads +++ b/gcc/ada/s-osinte-darwin.ads @@ -175,7 +175,7 @@ package System.OS_Interface is ---------- Time_Slice_Supported : constant Boolean := True; - -- Indicates wether time slicing is supported + -- Indicates whether time slicing is supported type timespec is private; @@ -284,9 +284,9 @@ package System.OS_Interface is -- No alternate signal stack is used on this platform Stack_Base_Available : constant Boolean := False; - -- Indicates wether the stack base is available on this target. This allows - -- us to share s-osinte.adb between all the FSU run time. Note that this - -- value can only be true if pthread_t has a complete definition that + -- Indicates whether the stack base is available on this target. This + -- allows us to share s-osinte.adb between all the FSU run time. Note that + -- this value can only be true if pthread_t has a complete definition that -- corresponds exactly to the C header files. function Get_Stack_Base (thread : pthread_t) return System.Address; diff --git a/gcc/ada/s-osinte-freebsd.ads b/gcc/ada/s-osinte-freebsd.ads index e0453ca90b4fe4b5a63dcad2ebaf47ac5e1047ae..51f498397f9528f3e89dd0f3c5e6f4f05da7fbaf 100644 --- a/gcc/ada/s-osinte-freebsd.ads +++ b/gcc/ada/s-osinte-freebsd.ads @@ -195,7 +195,7 @@ package System.OS_Interface is ---------- Time_Slice_Supported : constant Boolean := True; - -- Indicates wether time slicing is supported (i.e SCHED_RR is supported) + -- Indicates whether time slicing is supported (i.e SCHED_RR is supported) type timespec is private; @@ -313,9 +313,9 @@ package System.OS_Interface is -- No alternate signal stack is used on this platform Stack_Base_Available : constant Boolean := False; - -- Indicates wether the stack base is available on this target. This allows - -- us to share s-osinte.adb between all the FSU run time. Note that this - -- value can only be true if pthread_t has a complete definition that + -- Indicates whether the stack base is available on this target. This + -- allows us to share s-osinte.adb between all the FSU run time. Note that + -- this value can only be true if pthread_t has a complete definition that -- corresponds exactly to the C header files. function Get_Stack_Base (thread : pthread_t) return Address; diff --git a/gcc/ada/s-osinte-hpux.ads b/gcc/ada/s-osinte-hpux.ads index b22e20d81cf06349c1e5f5537c75b0be81d7e840..0fc5ef1db54ed9c1ca6637a635cdfd1b44d42330 100644 --- a/gcc/ada/s-osinte-hpux.ads +++ b/gcc/ada/s-osinte-hpux.ads @@ -177,7 +177,7 @@ package System.OS_Interface is ---------- Time_Slice_Supported : constant Boolean := True; - -- Indicates wether time slicing is supported + -- Indicates whether time slicing is supported type timespec is private; @@ -299,7 +299,7 @@ package System.OS_Interface is -- This must be in keeping with init.c:__gnat_alternate_stack Stack_Base_Available : constant Boolean := False; - -- Indicates wether the stack base is available on this target + -- Indicates whether the stack base is available on this target function Get_Stack_Base (thread : pthread_t) return Address; pragma Inline (Get_Stack_Base); diff --git a/gcc/ada/s-osinte-lynxos-3.adb b/gcc/ada/s-osinte-lynxos-3.adb index 01524c89251be47383d2888683b4f7b8857a1de4..09cbfca99b7a57120c970c7321225e0fc939d5b9 100644 --- a/gcc/ada/s-osinte-lynxos-3.adb +++ b/gcc/ada/s-osinte-lynxos-3.adb @@ -138,7 +138,7 @@ package body System.OS_Interface is -------------------------- -- For all the following functions, LynxOS threads has the POSIX Draft 4 - -- begavior; it sets errno but the standard Posix requires it to be + -- behavior; it sets errno but the standard Posix requires it to be -- returned. function pthread_mutexattr_init diff --git a/gcc/ada/s-osinte-lynxos-3.ads b/gcc/ada/s-osinte-lynxos-3.ads index 37c183b1f69d9c07b8d464a754de34fc44c11552..8098a8fbe881fba80147f96d65b2a7b7cd296b6a 100644 --- a/gcc/ada/s-osinte-lynxos-3.ads +++ b/gcc/ada/s-osinte-lynxos-3.ads @@ -175,7 +175,7 @@ package System.OS_Interface is ---------- Time_Slice_Supported : constant Boolean := True; - -- Indicates wether time slicing is supported + -- Indicates whether time slicing is supported type timespec is private; @@ -271,7 +271,7 @@ package System.OS_Interface is -- No alternate signal stack is used on this platform Stack_Base_Available : constant Boolean := False; - -- Indicates wether the stack base is available on this target + -- Indicates whether the stack base is available on this target function Get_Stack_Base (thread : pthread_t) return Address; pragma Inline (Get_Stack_Base); @@ -383,7 +383,7 @@ package System.OS_Interface is mutex : access pthread_mutex_t; reltime : access timespec) return int; pragma Inline (pthread_cond_timedwait); - -- LynxOS has a nonstandard pthrad_cond_timedwait + -- LynxOS has a nonstandard pthread_cond_timedwait Relative_Timed_Wait : constant Boolean := True; -- pthread_cond_timedwait requires a relative delay time diff --git a/gcc/ada/s-osinte-lynxos.ads b/gcc/ada/s-osinte-lynxos.ads index 13c2b88fcdb9dbcdb2f71fb2473f3650b4c248dc..dd30d2421760b4cb28c42db7118a3048e3643619 100644 --- a/gcc/ada/s-osinte-lynxos.ads +++ b/gcc/ada/s-osinte-lynxos.ads @@ -87,7 +87,7 @@ package System.OS_Interface is -- -- -- The lowest numbered signal is 1, but 0 is a valid argument to some - -- library functions, eg. kill(2). However, 0 is not just another + -- library functions, e.g. kill(2). However, 0 is not just another -- signal: For instance 'I in Signal' and similar should be used with -- caution. diff --git a/gcc/ada/s-osinte-rtems.ads b/gcc/ada/s-osinte-rtems.ads index 268eb43ac2162de06cab9e245083dbb135029540..f28e14d30831b29feadcb09faeee9e3a687b3e4b 100644 --- a/gcc/ada/s-osinte-rtems.ads +++ b/gcc/ada/s-osinte-rtems.ads @@ -159,7 +159,7 @@ package System.OS_Interface is ---------- Time_Slice_Supported : constant Boolean := True; - -- Indicates wether time slicing is supported (i.e SCHED_RR is supported) + -- Indicates whether time slicing is supported (i.e SCHED_RR is supported) type timespec is private; @@ -250,7 +250,7 @@ package System.OS_Interface is ----------- Stack_Base_Available : constant Boolean := False; - -- Indicates wether the stack base is available on this target. + -- Indicates whether the stack base is available on this target. -- This allows us to share s-osinte.adb between all the FSU/RTEMS -- run time. -- Note that this value can only be true if pthread_t has a complete diff --git a/gcc/ada/s-osinte-solaris-posix.ads b/gcc/ada/s-osinte-solaris-posix.ads index 05b328df26ad6481c7f8f73a6bd7d48601d34f47..ae318060ccd235db4d35804dda2cb81d281b69d2 100644 --- a/gcc/ada/s-osinte-solaris-posix.ads +++ b/gcc/ada/s-osinte-solaris-posix.ads @@ -185,7 +185,7 @@ package System.OS_Interface is ---------- Time_Slice_Supported : constant Boolean := True; - -- Indicates wether time slicing is supported + -- Indicates whether time slicing is supported type timespec is private; diff --git a/gcc/ada/s-osprim-mingw.adb b/gcc/ada/s-osprim-mingw.adb index e172388a24798b0db2315f846c1001283c9ee712..d9712858c395080e4aec3fb1c2640ead8d9ac9a4 100644 --- a/gcc/ada/s-osprim-mingw.adb +++ b/gcc/ada/s-osprim-mingw.adb @@ -130,10 +130,10 @@ package body System.OS_Primitives is Duration (Long_Long_Float (Current_Ticks - BTA.all) / Long_Long_Float (TFA.all)); - -- If we have a shift of more than Max_Shift seconds we resynchonize the - -- Clock. This is probably due to a manual Clock adjustment, an DST - -- adjustment or an NTP synchronisation. And we want to adjust the time - -- for this system (non-monotonic) clock. + -- If we have a shift of more than Max_Shift seconds we resynchronize + -- the Clock. This is probably due to a manual Clock adjustment, an + -- DST adjustment or an NTP synchronisation. And we want to adjust the + -- time for this system (non-monotonic) clock. if abs (Elap_Secs_Sys - Elap_Secs_Tick) > Max_Shift then Get_Base_Time; diff --git a/gcc/ada/s-osprim-vms.adb b/gcc/ada/s-osprim-vms.adb index 9bd8e61bff2648c4205e24c625d5644452434403..93138414571f7fb71a0d6e5a53241e82d6e82bec 100644 --- a/gcc/ada/s-osprim-vms.adb +++ b/gcc/ada/s-osprim-vms.adb @@ -71,7 +71,7 @@ package body System.OS_Primitives is -- pidadr = address of process id to be woken up -- prcnam = name of process to be woken up -- daytim = time to wake up - -- reptim = repitition interval of wakeup calls + -- reptim = repetition interval of wakeup calls -- procedure Sys_Schdwk diff --git a/gcc/ada/s-parame-ae653.ads b/gcc/ada/s-parame-ae653.ads index a2a5c0647e19fca695f2b6e93f5b4e9138d1c01f..5d4fd4caed82562a06b18b4471f2aeb76d6be41b 100644 --- a/gcc/ada/s-parame-ae653.ads +++ b/gcc/ada/s-parame-ae653.ads @@ -125,7 +125,7 @@ package System.Parameters is -- The system releases all storage on program termination only, -- but not other garbage collection occurs, so finalization calls - -- are ommitted only for outer level onjects can be omitted if + -- are omitted only for outer level objects can be omitted if -- pragma Finalize_Storage_Only is used. -- Garbage_Collected = True diff --git a/gcc/ada/s-parame-hpux.ads b/gcc/ada/s-parame-hpux.ads index 86bc0282e5151ef7e5e475a7c8a98d11f1c2c640..865ed763f44d21435fcb7939e59c3aceec31959e 100644 --- a/gcc/ada/s-parame-hpux.ads +++ b/gcc/ada/s-parame-hpux.ads @@ -123,7 +123,7 @@ package System.Parameters is -- The system releases all storage on program termination only, -- but not other garbage collection occurs, so finalization calls - -- are ommitted only for outer level onjects can be omitted if + -- are omitted only for outer level objects can be omitted if -- pragma Finalize_Storage_Only is used. -- Garbage_Collected = True diff --git a/gcc/ada/s-parame-vms-alpha.ads b/gcc/ada/s-parame-vms-alpha.ads index 6df2a47aa1238621716f164539c68e174bbc8485..b9119bc00d7a041d52eff443d04128db15ba7b21 100644 --- a/gcc/ada/s-parame-vms-alpha.ads +++ b/gcc/ada/s-parame-vms-alpha.ads @@ -123,7 +123,7 @@ package System.Parameters is -- The system releases all storage on program termination only, -- but not other garbage collection occurs, so finalization calls - -- are ommitted only for outer level onjects can be omitted if + -- are omitted only for outer level objects can be omitted if -- pragma Finalize_Storage_Only is used. -- Garbage_Collected = True diff --git a/gcc/ada/s-parame-vms-ia64.ads b/gcc/ada/s-parame-vms-ia64.ads index 10332527a6815a7291666b8622e788d2c9b4b6ff..4273df9dd95001d37c9e63e660f3aef40b8f33bc 100644 --- a/gcc/ada/s-parame-vms-ia64.ads +++ b/gcc/ada/s-parame-vms-ia64.ads @@ -123,7 +123,7 @@ package System.Parameters is -- The system releases all storage on program termination only, -- but not other garbage collection occurs, so finalization calls - -- are ommitted only for outer level onjects can be omitted if + -- are omitted only for outer level objects can be omitted if -- pragma Finalize_Storage_Only is used. -- Garbage_Collected = True diff --git a/gcc/ada/s-parame-vms-restrict.ads b/gcc/ada/s-parame-vms-restrict.ads index 6cd0477502363452913ca48ff551d499c2da2426..a0404edaac2681273dbd71a5ee2f822159a16a15 100644 --- a/gcc/ada/s-parame-vms-restrict.ads +++ b/gcc/ada/s-parame-vms-restrict.ads @@ -123,7 +123,7 @@ package System.Parameters is -- The system releases all storage on program termination only, -- but not other garbage collection occurs, so finalization calls - -- are ommitted only for outer level onjects can be omitted if + -- are omitted only for outer level objects can be omitted if -- pragma Finalize_Storage_Only is used. -- Garbage_Collected = True diff --git a/gcc/ada/s-parame-vxworks.ads b/gcc/ada/s-parame-vxworks.ads index 4f7cc2c7fcbb956ab0695f588eef4b24f710e374..bc0ee16ca60bd25d74d512930f0691cb75d69465 100644 --- a/gcc/ada/s-parame-vxworks.ads +++ b/gcc/ada/s-parame-vxworks.ads @@ -125,7 +125,7 @@ package System.Parameters is -- The system releases all storage on program termination only, -- but not other garbage collection occurs, so finalization calls - -- are ommitted only for outer level onjects can be omitted if + -- are omitted only for outer level objects can be omitted if -- pragma Finalize_Storage_Only is used. -- Garbage_Collected = True diff --git a/gcc/ada/s-parame.ads b/gcc/ada/s-parame.ads index 20c95bea0c447218a29582efe604657b7c08cee9..a94b22296bc91a8b923e7db831a881c17c46ef85 100644 --- a/gcc/ada/s-parame.ads +++ b/gcc/ada/s-parame.ads @@ -123,7 +123,7 @@ package System.Parameters is -- The system releases all storage on program termination only, -- but not other garbage collection occurs, so finalization calls - -- are ommitted only for outer level onjects can be omitted if + -- are omitted only for outer level objects can be omitted if -- pragma Finalize_Storage_Only is used. -- Garbage_Collected = True diff --git a/gcc/ada/s-parint.adb b/gcc/ada/s-parint.adb index 622c2d0106273a6a5e3610fdef3f8b0b6d018ca1..94b08326c25bc002786ee4863de591a229523d7a 100644 --- a/gcc/ada/s-parint.adb +++ b/gcc/ada/s-parint.adb @@ -34,7 +34,7 @@ package body System.Partition_Interface is - pragma Warnings (Off); -- supress warnings for unreferenced formals + pragma Warnings (Off); -- suppress warnings for unreferenced formals M : constant := 7; diff --git a/gcc/ada/s-parint.ads b/gcc/ada/s-parint.ads index 39b96c97deae23d2d591edbff3f6e0adb7a9b80f..9191c0731b65544a8cdd1e30d801f57c51f64ea9 100644 --- a/gcc/ada/s-parint.ads +++ b/gcc/ada/s-parint.ads @@ -94,7 +94,7 @@ package System.Partition_Interface is pragma No_Strict_Aliasing (RAS_Proxy_Type_Access); -- This type is used by the expansion to implement distributed objects. -- Do not change its definition or its layout without updating - -- Exp_Dist.Build_Remote_Supbrogram_Proxy_Type. + -- Exp_Dist.Build_Remote_Subprogram_Proxy_Type. -- The Request_Access type is used for communication between the PCS -- and the RPC receiver generated by the compiler: it contains all the diff --git a/gcc/ada/s-poosiz.adb b/gcc/ada/s-poosiz.adb index a86f1d113fc8d66eef27f3b9595439b7686a32db..5d7318da3eb545400d17d5a2ac3a764e1b0967c5 100644 --- a/gcc/ada/s-poosiz.adb +++ b/gcc/ada/s-poosiz.adb @@ -59,7 +59,7 @@ package body System.Pool_Size is -- Embedded pool that manages allocation of variable-size data - -- This pool is used as soon as the Elmt_sizS of the pool object is 0 + -- This pool is used as soon as the Elmt_Size of the pool object is 0 -- Allocation is done on the first chunk long enough for the request. -- Deallocation just puts the freed chunk at the beginning of the list. @@ -261,7 +261,7 @@ package body System.Pool_Size is raise Storage_Error; end if; - -- When the chunk is bigger than what is needed, take appropraite + -- When the chunk is bigger than what is needed, take appropriate -- amount and build a new shrinked chunk with the remainder. if Size (Pool, Chunk) - Align_Size > Minimum_Size then diff --git a/gcc/ada/s-proinf-irix-athread.ads b/gcc/ada/s-proinf-irix-athread.ads index 83fff2611175ba92548e4e5469a3a86ad45570c2..aa266ac924d495e6f27e62b35f0928f30dd04876 100644 --- a/gcc/ada/s-proinf-irix-athread.ads +++ b/gcc/ada/s-proinf-irix-athread.ads @@ -56,7 +56,7 @@ package System.Program_Info is function Default_Task_Stack return Integer; -- The default stack size for each created thread. This default value can - -- be overriden on a per-task basis by the language-defined Storage_Size + -- be overridden on a per-task basis by the language-defined Storage_Size -- pragma. function Stack_Guard_Pages return Integer; diff --git a/gcc/ada/s-proinf.ads b/gcc/ada/s-proinf.ads index 2a4e78e9766212ac2413a80566a421b9daf721a4..f5133d66ad1d70f878cd9bb28f73424519e461c5 100644 --- a/gcc/ada/s-proinf.ads +++ b/gcc/ada/s-proinf.ads @@ -39,7 +39,7 @@ package System.Program_Info is function Default_Task_Stack return Integer; -- The default stack size for each created thread. This default value - -- can be overriden on a per-task basis by the language-defined + -- can be overridden on a per-task basis by the language-defined -- Storage_Size pragma. end System.Program_Info; diff --git a/gcc/ada/s-regexp.adb b/gcc/ada/s-regexp.adb index c548199b49feee5729b4ce08210c1cd5e3f1589f..2dae7b2910375a2cc5c3962f6398b96280fcf95f 100755 --- a/gcc/ada/s-regexp.adb +++ b/gcc/ada/s-regexp.adb @@ -140,7 +140,7 @@ package body System.Regexp is Num_States : out State_Index; Start_State : out State_Index; End_State : out State_Index); - -- Creates the first version of the regexp (this is a non determinist + -- Creates the first version of the regexp (this is a non deterministic -- finite state machine, which is unadapted for a fast pattern -- matching algorithm). We use a recursive algorithm to process the -- parenthesis sub-expressions. @@ -1137,7 +1137,7 @@ package body System.Regexp is end loop; end Closure; - -- Start of procesing for Create_Secondary_Table + -- Start of processing for Create_Secondary_Table begin -- Create a new state diff --git a/gcc/ada/s-regpat.adb b/gcc/ada/s-regpat.adb index 95bc4bc16b1f51396fe6c17112fc27fce3939d1b..68d915f8ad0f5417d2ec58262dec9237c6b79880 100755 --- a/gcc/ada/s-regpat.adb +++ b/gcc/ada/s-regpat.adb @@ -136,10 +136,10 @@ package body System.Regpat is -- Matches after or before a word BOL, -- no Match "" at beginning of line - MBOL, -- no Same, assuming mutiline (match after \n) + MBOL, -- no Same, assuming multiline (match after \n) SBOL, -- no Same, assuming single line (don't match at \n) EOL, -- no Match "" at end of line - MEOL, -- no Same, assuming mutiline (match before \n) + MEOL, -- no Same, assuming multiline (match before \n) SEOL, -- no Same, assuming single line (don't match at \n) BOUND, -- no Match "" at any word boundary @@ -386,7 +386,7 @@ package body System.Regpat is function Emit_Node (Op : Opcode) return Pointer; -- If code-generation is enabled, Emit_Node outputs the -- opcode Op and reserves space for a pointer to the next node. - -- Return value is the location of new opcode, ie old Emit_Ptr. + -- Return value is the location of new opcode, i.e. old Emit_Ptr. procedure Emit_Natural (IP : Pointer; N : Natural); -- Split N on two characters at position IP @@ -449,7 +449,7 @@ package body System.Regpat is -- Link_Tail sets the next-pointer at the end of a node chain procedure Link_Operand_Tail (P, Val : Pointer); - -- Link_Tail on operand of first argument; nop if operandless + -- Link_Tail on operand of first argument; noop if operand-less function Next_Instruction (P : Pointer) return Pointer; -- Dig the "next" pointer out of a node @@ -460,7 +460,7 @@ package body System.Regpat is function Is_Curly_Operator (IP : Natural) return Boolean; -- Return True if IP is looking at a '{' that is the beginning - -- of a curly operator, ie it matches {\d+,?\d*} + -- of a curly operator, i.e. it matches {\d+,?\d*} function Is_Mult (IP : Natural) return Boolean; -- Return True if C is a regexp multiplier: '+', '*' or '?' @@ -484,8 +484,8 @@ package body System.Regpat is -- Parse_Literal encodes a string of characters to be matched exactly function Parse_Posix_Character_Class return Std_Class; - -- Parse a posic character class, like [:alpha:] or [:^alpha:]. - -- The called is suppoed to absorbe the opening [. + -- Parse a posix character class, like [:alpha:] or [:^alpha:]. + -- The caller is supposed to absorb the opening [. pragma Inline (Is_Mult); pragma Inline (Emit_Natural); diff --git a/gcc/ada/s-regpat.ads b/gcc/ada/s-regpat.ads index 64429b246428d8db0e01cedf2895081f075126a4..077518dd903cad16634151262f3110b0e6e479db 100755 --- a/gcc/ada/s-regpat.ads +++ b/gcc/ada/s-regpat.ads @@ -414,7 +414,7 @@ package System.Regpat is -- approach, in addition to the improved efficiency, is that the same -- Pattern_Matcher variable can be used to hold the compiled code for -- several different regular expressions by setting a size that is large - -- enough to accomodate all possibilities. + -- enough to accommodate all possibilities. -- -- In this version of the procedure call, the actual required code size is -- returned. Also if Matcher.Size is zero on entry, then the resulting code diff --git a/gcc/ada/s-rident.ads b/gcc/ada/s-rident.ads index 68a5197266fae45f795bf82bab88557c87938fa6..c28ba3c5a92f8788698265d6a13b70e706ae53cd 100644 --- a/gcc/ada/s-rident.ads +++ b/gcc/ada/s-rident.ads @@ -191,7 +191,7 @@ package System.Rident is -- Boolean restrictions that are not checked for partition consistency -- and that thus apply only to the current unit. Note that for these -- restrictions, the compiler does not apply restrictions found in - -- with'ed units, parent specs etc to the main unit. + -- with'ed units, parent specs etc. to the main unit. subtype All_Parameter_Restrictions is Restriction_Id range @@ -305,7 +305,7 @@ package System.Rident is ---------------------------------- type Profile_Name is (Ravenscar, Restricted); - -- Names of recognized pfofiles + -- Names of recognized profiles type Profile_Data is record Set : Restriction_Flags;