+2008-04-14 Ralf Wildenhues <Ralf.Wildenhues@gmx.de>
+
+ * vms_data.ads: Fix typo in constant.
+ * gen-soccon.c: Fix typo in error string.
+ * gnat_rm.texi (Pragma Optimize_Alignment, Pragma Postcondition):
+ Fix typos.
+ * a-calcon.ads, a-calend-vms.adb, a-calend.adb, a-crdlli.ads,
+ bcheck.adb, checks.adb, einfo.ads, errout.adb, erroutc.adb,
+ erroutc.ads, exp_attr.adb, exp_ch11.adb, exp_ch2.adb,
+ exp_ch5.adb, exp_ch9.adb, exp_ch9.ads, exp_pakd.adb,
+ exp_util.adb, fmap.adb, g-soccon-linux-mips.ads,
+ g-soccon-rtems.ads, g-timsta.adb, g-timsta.ads, lib-writ.ads,
+ mlib-tgt-specific-linux.adb, mlib-tgt-specific-tru64.adb,
+ s-interr-vxworks.adb, s-interr.adb, s-osinte-lynxos.ads,
+ s-rident.ads, s-taprop-solaris.adb, s-tassta.adb, s-win32.ads,
+ sem_aggr.adb, sem_attr.ads, sem_ch10.adb, sem_ch13.ads,
+ sem_ch3.adb, sem_ch6.adb, sem_ch7.adb, sem_ch8.adb, sem_ch9.adb,
+ sem_prag.ads, sem_res.adb, sem_util.adb, sem_util.ads,
+ sinfo.ads: Fix typos in comments.
+
2008-04-14 Robert Dewar <dewar@adacore.com>
* sem_prag.adb (Analyze_Pragma, Linker_Section case): Extend error
-- The returned value is in UTC and may or may not contain leap seconds
-- depending on whether binder flag "-y" was used. Raises Time_Error if
-- the input values are out of the defined ranges or if tm_sec equals 60
- -- and the instance in time is not a leap second occurence.
+ -- and the instance in time is not a leap second occurrence.
function To_Duration
(tv_sec : Interfaces.C.long;
tm_year := Year - 1900;
tm_mon := Month - 1;
- -- Step 3: Handle leap second occurences
+ -- Step 3: Handle leap second occurrences
if Leap_Sec then
tm_sec := 60;
tm_year := Year - 1900;
tm_mon := Month - 1;
- -- Step 3: Handle leap second occurences
+ -- Step 3: Handle leap second occurrences
if Leap_Sec then
tm_sec := 60;
Position : Cursor := No_Element) return Cursor;
-- Searches for the node whose element is equal to Item, starting from
-- Position and continuing to the last end of the list. If Position equals
- -- No_Element, the seach starts from the first node. If Position is
+ -- No_Element, the search starts from the first node. If Position is
-- associated with a list object different from Container, then
-- Program_Error is raised. If no node is found having an element equal to
-- Item, then Find returns No_Element.
Position : Cursor := No_Element) return Cursor;
-- Searches in reverse for the node whose element is equal to Item,
-- starting from Position and continuing to the first end of the list. If
- -- Position equals No_Element, the seach starts from the last node. If
+ -- Position equals No_Element, the search starts from the last node. If
-- Position is associated with a list object different from Container, then
-- Program_Error is raised. If no node is found having an element equal to
-- Item, then Reverse_Find returns No_Element.
-----------------------------------------
-- The rule is that all units which depend on the global default setting
- -- of Optimize_Alignment must be compiled with the same settinng for this
+ -- of Optimize_Alignment must be compiled with the same setting for this
-- default. Units which specify an explicit local value for this setting
-- are exempt from the consistency rule (this includes all internal units).
-- Check that a null-excluding component, formal or object is not being
-- assigned a null value. Otherwise generate a warning message and
- -- replace Expression (N) by an N_Contraint_Error node.
+ -- replace Expression (N) by an N_Constraint_Error node.
if K /= N_Function_Specification then
Expr := Expression (N);
-- for finalization purposes, The block entity has an implicit label
-- declaration in the enclosing declarative part, and has otherwise
-- no direct connection in the tree with the block statement. The
--- link is to the identifier (which is an occurence of the entity)
+-- link is to the identifier (which is an occurrence of the entity)
-- and not to the block_statement itself, because the statement may
-- be rewritten, e.g. in the process of removing dead code.
-- component clause applies to the component. First bit position of
-- given component, computed from the first bit and position values
-- given in the component clause. A value of No_Uint means that the
--- value is not yet known. The value can be set by the appearence of
+-- value is not yet known. The value can be set by the appearance of
-- an explicit component clause in a record representation clause,
-- or it can be set by the front-end in package Layout, or it can be
-- set by the backend. By the time backend processing is completed,
-- Elaboration_Entity (Node13)
-- Present in generic and non-generic package and subprogram
-- entities. This is a boolean entity associated with the unit that
--- is initiallly set to False, and is set True when the unit is
+-- is initially set to False, and is set True when the unit is
-- elaborated. This is used for two purposes. First, it is used to
-- implement required access before elaboration checks (the flag
-- must be true to call a subprogram at elaboration time). Second,
-- Present in subprogram entities. Points to a list of Precondition
-- and Postcondition N_Pragma nodes for preconditions and postconditions
-- declared in the spec. The last pragma encountered is at the head of
--- this list, so it is in reverse order of textual appearence.
+-- this list, so it is in reverse order of textual appearance.
-- Storage_Size_Variable (Node15) [implementation base type only]
-- Present in access types and task type entities. This flag is set
-- required discriminant values. The expander creates a set of declarations
-- of the form:
- -- discr_nameD : constant disrc_type renames _task.discr_name;
+ -- discr_nameD : constant discr_type renames _task.discr_name;
-- where discr_nameD is the discriminal entity referenced by the task
-- discriminant, and _task is the task value passed in as the parameter.
procedure VMS_Convert;
-- This procedure has no effect if called when the host is not OpenVMS.
-- If the host is indeed OpenVMS, then the error message stored in
- -- Msg_Buffer is scanned for appearences of switch names which need
- -- converting to corresponding VMS qualifer names. See Gnames/Vnames
+ -- Msg_Buffer is scanned for appearances of switch names which need
+ -- converting to corresponding VMS qualifier names. See Gnames/Vnames
-- table in Errout spec for precise definition of the conversion that
-- is performed by this routine in OpenVMS mode.
else
Start := Ptr;
- -- First scan forward looing for a hard end of line
+ -- First scan forward looking for a hard end of line
for Scan in Ptr .. Ptr + Max - 1 loop
if Txt (Scan) = ASCII.LF then
Is_Style_Msg : Boolean := False;
-- Set True to indicate if the current message is a style message
- -- (i.e. a message whose text starts with the cahracters "(style)").
+ -- (i.e. a message whose text starts with the characters "(style)").
Is_Serious_Error : Boolean := False;
-- Set by Set_Msg_Text to indicate if current message is serious error
-- sourcetyp (streamread (strmtyp'Input (stream)));
- -- where stmrearead is the given Read function that converts an
+ -- where streamread is the given Read function that converts an
-- argument of type strmtyp to type sourcetyp or a type from which
-- it is derived (extra conversion required for the derived case).
-- result is modulus + value, where the value might be as small as
-- -modulus. The trouble is what type do we use to do the subtract.
-- No type will do, since modulus can be as big as 2**64, and no
- -- integer type accomodates this value. Let's do bit of algebra
+ -- integer type accommodates this value. Let's do bit of algebra
-- modulus + value
-- = modulus - (-value)
begin
-- If we have no Entity, then we are probably in no run time mode
- -- or some weird error has occured. In either case do do nothing!
+ -- or some weird error has occurred. In either case do do nothing!
if Present (Ent) then
declare
end if;
-- If constant value is an occurrence of an enumeration literal,
- -- then we just make another occurence of the same literal.
+ -- then we just make another occurrence of the same literal.
if Is_Entity_Name (Val)
and then Ekind (Entity (Val)) = E_Enumeration_Literal
-- we also generate an extra parameter to hold the Constrained
-- attribute of the actual. No renaming is generated for this flag.
- -- Calling Node_Posssible_Modifications in the expander is dubious,
+ -- Calling Node_Possible_Modifications in the expander is dubious,
-- because this generates a cross-reference entry, and should be
-- done during semantic processing so it is called in -gnatc mode???
procedure Expand_N_Simple_Return_Statement (N : Node_Id) is
begin
- -- Defend agains previous errors (ie. the return statement calls a
+ -- Defend against previous errors (i.e. the return statement calls a
-- function that is not available in configurable runtime).
if Present (Expression (N))
(Loc : Source_Ptr;
Def_Id : Entity_Id;
Ent_Id : Entity_Id) return Node_Id;
- -- Build a specification for the procedure implementing the statemens of
+ -- Build a specification for the procedure implementing the statements of
-- the specified entry body. Add attributes associating it with the entry
-- defining identifier Ent_Id.
Add_Object_Pointer (Loc, Pid, Op_Decls);
-- Add renamings for all formals, the Protection object, discriminals,
- -- privals and the entry indix constant for use by debugger.
+ -- privals and the entry index constant for use by debugger.
Add_Formal_Renamings (Espec, Op_Decls, Ent, Loc);
Debug_Private_Data_Declarations (Decls);
begin
-- Add renamings for the Protection object, discriminals, privals and
- -- the entry indix constant for use by debugger.
+ -- the entry index constant for use by debugger.
Debug_Private_Data_Declarations (Decls);
procedure Set_Discriminals (Dec : Node_Id);
-- Replace discriminals in a protected type for use by the next protected
- -- operation on the type. Each operation needs a new set of discirminals,
+ -- operation on the type. Each operation needs a new set of discriminals,
-- since it needs a unique renaming of the discriminant fields in the
-- record used to implement the protected type.
Ltyp := Etype (L);
Rtyp := Etype (R);
- -- Deeal with silly case of XOR where the subcomponent has a range
+ -- Deal with silly case of XOR where the subcomponent has a range
-- True .. True where an exception must be raised.
if Nkind (N) = N_Op_Xor then
-- A protected type without entries that covers an interface and
-- overrides the abstract routines with protected procedures is
-- considered equivalent to a protected type with entries in the
- -- context of dispatching select statements. It is sufficent to
+ -- context of dispatching select statements. It is sufficient to
-- check for the presence of an interface list in the declaration
-- node to recognize this case.
-- Most predefined primitives have internally generated names. Equality
-- must be treated differently; the predefined operation is recognized
- -- as a homgeneous binary operator that returns Boolean.
+ -- as a homogeneous binary operator that returns Boolean.
if Name_Len > TSS_Name_Type'Last then
TSS_Name := TSS_Name_Type (Name_Buffer (Name_Len - TSS_Name'Length + 1
No_Mapping_File : Boolean := False;
-- Set to True when the specified mapping file cannot be read in
- -- procedure Initialize, so that no attempt is made to oopen the mapping
+ -- procedure Initialize, so that no attempt is made to open the mapping
-- file in procedure Update_Mapping_File.
function To_Big_String_Ptr is new Unchecked_Conversion
-- --
-- S p e c --
-- --
--- Copyright (C) 2000-2005, Free Software Foundation, Inc. --
+-- Copyright (C) 2000-2008, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- This is the version for mips-linux, manually edited for the first shot
-- no mips hardware at hand
-- using http://www.gelato.unsw.edu.au/lxr/source/include/asm-mips/socket.h
--- in order to find differents values
+-- in order to find different values.
-- This file is generated automatically, do not modify it by hand! Instead,
-- make changes to gen-soccon.c and re-run it on each target.
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
-- --
-- S p e c --
-- --
--- Copyright (C) 2000-2007, Free Software Foundation, Inc. --
+-- Copyright (C) 2000-2008, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
EINVAL : constant := 22; -- Invalid argument
EIO : constant := 5; -- Input output error
EISCONN : constant := 127; -- Socket already connected
- ELOOP : constant := 92; -- Too many symbolic lynks
+ ELOOP : constant := 92; -- Too many symbolic links
EMFILE : constant := 24; -- Too many open files
EMSGSIZE : constant := 122; -- Message too long
ENAMETOOLONG : constant := 91; -- Name too long
type time_stamp_ptr is access all time_stamp;
-- The desired ISO 8601 string format has exactly 22 characters. We add
-- one additional character for '\0'. The indexing starts from zero to
- -- accomodate the C layout.
+ -- accommodate the C layout.
procedure gnat_current_time_string (Value : time_stamp_ptr);
pragma Import (C, gnat_current_time_string, "__gnat_current_time_string");
-- --
------------------------------------------------------------------------------
--- This package provides a lighweight mechanism for obtaining time stamps
+-- This package provides a lightweight mechanism for obtaining time stamps
package GNAT.Time_Stamp is
#ifndef ELOOP
#define ELOOP -1
#endif
-CND(ELOOP, "Too many symbolic lynks")
+CND(ELOOP, "Too many symbolic links")
#ifndef EMFILE
#define EMFILE -1
pragma file containing the appropriate setting. The exception to this rule is
that units with an explicit configuration pragma in the same file as the source
unit are excluded from the consistency check, as are all predefined units. The
-latter are commpiled by default in pragma Optimize_Alignment (Off) mode if no
+latter are compiled by default in pragma Optimize_Alignment (Off) mode if no
pragma appears at the start of the file.
@node Pragma Passive
argument was supplied, then the default message has
the form "Postcondition failed at file:line". The
exception is raised in the context of the subprogram
-body, so it is posssible to catch postcondition failures
+body, so it is possible to catch postcondition failures
within the subprogram body itself.
Within a package spec, normal visibility rules
-- elaboration code is required. Set if N_Compilation_Unit
-- node has flag Has_No_Elaboration_Code set.
--
- -- OL The units in this file are commpiled with a local pragma
+ -- OL The units in this file are compiled with a local pragma
-- Optimize_Alignment, so no consistency requirement applies
-- to these units. All internal units have this status since
-- they have an automatic default of Optimize_Alignment (Off).
-- units in this file. All files in the partition that specify
-- a default must specify the same default.
--
- -- OS Optimize_Alignment (Space) is the default settinng for all
+ -- OS Optimize_Alignment (Space) is the default setting for all
-- units in this file. All files in the partition that specify
-- a default must specify the same default.
--
- -- OT Optimize_Alignment (Time) is the default settinng for all
+ -- OT Optimize_Alignment (Time) is the default setting for all
-- units in this file. All files in the partition that specify
-- a default must specify the same default.
--
-- --
-- B o d y --
-- --
--- Copyright (C) 2001-2007, Free Software Foundation, Inc. --
+-- Copyright (C) 2001-2008, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
pragma Unreferenced (Interfaces);
pragma Unreferenced (Symbol_Data);
pragma Unreferenced (Auto_Init);
- -- Initialization is done through the contructor mechanism
+ -- Initialization is done through the constructor mechanism
Lib_File : constant String :=
"lib" & Fil.Append_To (Lib_Filename, DLL_Ext);
-- --
------------------------------------------------------------------------------
--- This is the True64 version of the body
+-- This is the Tru64 version of the body
with MLib.Fil;
with MLib.Utl;
-- signals and exceptions). As opposed to the signal implementation,
-- this handler is installed in the vector table when the first Ada
-- handler is attached to the interrupt. However because VxWorks don't
- -- support disconnecting handlers, this subprogram always test wether
+ -- support disconnecting handlers, this subprogram always test whether
-- or not an Ada handler is effectively attached.
-- Otherwise, the handler that existed prior to program startup is
-- There are two Interrupt interrupts that this task catch through
-- "sigwait." One is the Interrupt this task is designated to catch
- -- in order to execure user handler or entry. The other one is the
+ -- in order to execute user handler or entry. The other one is the
-- Abort_Task_Interrupt. This interrupt is being sent from the
-- Interrupt_Manager to inform status changes (e.g: become Blocked,
-- Handler or Entry is to be detached).
SA_SIGINFO : constant := 16#80#;
SA_ONSTACK : constant := 16#00#;
- -- SA_ONSTACK is not defined on LynxOS, but it is refered to in the POSIX
+ -- SA_ONSTACK is not defined on LynxOS, but it is referred to in the POSIX
-- implementation of System.Interrupt_Management. Therefore we define a
-- dummy value of zero here so that setting this flag is a nop.
-- If an entry for a parameter restriction is True in Violated, the
-- corresponding entry in the Unknown array may record additional
-- information. If the actual count is not known by the compiler (but
- -- is nown to be non-zero), then the entry in Unknown will be True.
+ -- is known to be non-zero), then the entry in Unknown will be True.
-- This indicates that the value in Count is not known to be exact,
-- and the actual violation count may be higher.
-- and priority handling.
Using_Real_Time_Class : Boolean := False;
- -- indicates whether the real time class is being used (i.e the process
+ -- indicates whether the real time class is being used (i.e. the process
-- has root privileges).
Prio_Param : aliased struct_pcparms;
-- Terminate_Task --
--------------------
- -- Before we allow the thread to exit, we must clean up. This is a a
+ -- Before we allow the thread to exit, we must clean up. This is a
-- delicate job. We must wake up the task's master, who may immediately try
-- to deallocate the ATCB out from under the current task WHILE IT IS STILL
-- EXECUTING.
------------------------------------------------------------------------------
-- This package plus its child provide the low level interface to the Win32
--- API. The core part of the Win32 API (commont to RTX and Win32) is in this
+-- API. The core part of the Win32 API (common to RTX and Win32) is in this
-- package, and an additional part of the Win32 API which is not supported by
-- RTX is in package System.Win33.Ext.
end if;
end if;
- -- If no others, aggregate bounds come from aggegate
+ -- If no others, aggregate bounds come from aggregate
Aggr_Low := Choices_Low;
Aggr_High := Choices_High;
-- is identical to the value that would be set if Initialize_Scalars
-- mode were in effect (including the behavior of its value on
-- environment variables or binder switches). The intended use is
- -- to set a value where intialization is required (e.g. as a result of
+ -- to set a value where initialization is required (e.g. as a result of
-- the coding standards in use), but logically no initialization is
-- needed, and the value should never be accessed.
end loop;
-- Now check incomplete declarations to locate Taft amendment
- -- types. This can be done by examing the defining identifiers
+ -- types. This can be done by examining the defining identifiers
-- of type declarations without real semantic analysis.
declare
-- attributes, clearly should not be subject to the para 10 restrictions
-- (see AI95-00137). Similarly, we also skip the para 10 restrictions for
-- the Storage_Size case where they also clearly do not apply, and for
- -- Stream_Convert which is in the same category as the strem attributes.
+ -- Stream_Convert which is in the same category as the stream attributes.
--
-- If the rep item is too late, an appropriate message is output and
-- True is returned, which is a signal that the caller should abandon
-- The current object is a discriminal generated for an entry
-- family index. Even though the index is a constant, in this
- -- particular context there is no true contant redeclaration.
+ -- particular context there is no true constant redeclaration.
-- Enter_Name will handle the visibility.
or else
if Present (Alias_Subp) then
-- Only perform the check for a derived subprogram when the
- -- type has an explicit record extension. This avoids incorect
+ -- type has an explicit record extension. This avoids incorrect
-- flagging of abstract subprograms for the case of a type
-- without an extension that is derived from a formal type
-- with a tagged actual (can occur within a private part).
-- If we are creating a renaming for a primitive operation of an
-- actual of a generic derived type, we must examine the signature
- -- of the actual primive, not that of the generic formal, which for
+ -- of the actual primitive, not that of the generic formal, which for
-- example may be an interface. However the name and initial value
-- of the inherited operation are those of the formal primitive.
Process_PPCs (N, Spec_Id, Body_Id);
- -- Add a declaration for the Protection objcect, renaming declarations
+ -- Add a declaration for the Protection object, renaming declarations
-- for discriminals and privals and finally a declaration for the entry
-- family index (if applicable). This form of early expansion is done
-- when the Expander is active because Install_Private_Data_Declarations
-- is both unnecessary and wrong, because it would cause the
-- clauses to be chained to themselves in the use clauses
-- list of the scope stack entry. That in turn would cause
- -- an endless loop from End_Use_Clauses upon sccope exit.
+ -- an endless loop from End_Use_Clauses upon scope exit.
-- The parent is now fully visible. It may be a hidden open
-- scope if we are currently compiling some child instance
begin
-- If the full view is a scalar type, the type is the anonymous
-- base type, but the operation mentions the first subtype, so
- -- check the signature againt the base type.
+ -- check the signature against the base type.
if Base_Type (Etype (S)) = Base_Type (T) then
return True;
-- If the renamed entity is a private protected component,
-- reference the original component as well. This needs to be
-- done because the private renamings are installed before any
- -- analysis has occured. Reference to a private component will
+ -- analysis has occurred. Reference to a private component will
-- resolve to the renaming and the original component will be
-- left unreferenced, hence the following.
-- all itypes within are frozen. This ensures that no freeze nodes
-- will be generated for them.
--
- -- On the other hand, components of the correesponding record are
+ -- On the other hand, components of the corresponding record are
-- frozen (or receive itype references) as for other records.
--------------------
-- Precondition, and Postcondition to determine if Check pragmas (or
-- corresponding Assert, Precondition, or Postcondition pragmas) are
-- currently active, as determined by the presence of -gnata on the
- -- command line (which sets the default), and the appearence of pragmas
+ -- command line (which sets the default), and the appearance of pragmas
-- Check_Policy and Assertion_Policy as configuration pragmas either in
-- a configuration pragma file, or at the start of the current unit.
-- True is returned if the specified check is enabled.
D : Node_Id;
begin
- -- Any use in a a spec-expression is legal
+ -- Any use in a spec-expression is legal
if In_Spec_Expression then
null;
if In_Spec_Expression then
return Empty;
- -- More commments for the rest of this body would be good ???
+ -- More comments for the rest of this body would be good ???
elsif Nkind (N) = N_Explicit_Dereference then
if Is_Composite_Type (T)
procedure Set_Optimize_Alignment_Flags (E : Entity_Id);
pragma Inline (Set_Optimize_Alignment_Flags);
- -- Sets Optimize_Aliignment_Space/Time flags in E from current settings
+ -- Sets Optimize_Alignment_Space/Time flags in E from current settings
procedure Set_Public_Status (Id : Entity_Id);
-- If an entity (visible or otherwise) is defined in a library
-- Next_Pragma (Node1-Sem)
-- Present in N_Pragma nodes. Used to create a linked list of pragma
- -- nodes. Curently used for two purposes:
+ -- nodes. Currently used for two purposes:
--
-- Create a list of linked Check_Policy pragmas. The head of this list
-- is stored in Opt.Check_Policy_List (which has further details).
"ALL_ON " &
"--coupling-all " &
"ALL_OFF " &
- "--no-counling-all " &
+ "--no-coupling-all " &
"PACKAGE_EFFERENT_ON " &
"--package-efferent-coupling " &
"PACKAGE_EFFERENT_OFF " &