Commit ba1cbfb9 by Robert Dewar Committed by Arnaud Charlet

debug.adb: Update flags documentation

2006-10-31  Robert Dewar  <dewar@adacore.com>
	    Cyrille Comar  <comar@adacore.com>
	    Ben Brosgol  <brosgol@adacore.com>

	* debug.adb:  Update flags documentation

        * gnat_ugn.texi: Add documentation for new -gnatwq switch
        Clean up documentation for several other warning switches
        Clarify how task stack size can be specified with various
        versions of Windows.
        Add note that -gnatVo includes ranges including loops
	Add documentation for -gnatL switch
	Add note on elaboration warning for initializing variables
	Add documentation for new -gnatwt warning switch
	Document new form of pragma Warnings (On|Off, string)
	Add comment on use of pragma Warnings to control warnings
	Add documentation for -gnatjnn switch
	Modify section on interfacing with C for VMS 64-bit.
	Add doc for -gnatVe/E
	Add documentation of new warning flags -gnatww/-gnatwW
	Add warnings about address clause overlays to list of warnings
	(Exception Handling Control): Document that the option --RTS must be
	used consistently for gcc and gnatbind.
	Clarify that inlining is not always possible
	Update documentation on pragma Unchecked_Union.

	* gnat_rm.texi: 
	Add documentation for new extended version of pragma Obsolescent
	Add documentation for implementation defined attribute 'Stub_Type.
	Add note on use of Volatile in asm statements
	Add documentation on use of pragma Unreferenced in context clause
	Document new form of pragma Warnings (On|Off, pattern)
	Document pragma Wide_Character_Encoding
	Add note that pragma Restrictions (No_Elaboration_Code) is only fully
	enforced if code generation is active.
	Add section on pragma Suppress to document GNAT specific check
	Alignment_Check
	Clarify difference between No_Dispatching_Calls & No_Dispatch.
	Add documentation for pragma Restrictions (No_Elaboration_Code)

	* gnat-style.texi: 
	Add comments on layout of subprogram local variables in the
	presence of nested subprograms.

        * ug_words: Resync.

	* elists.ads: Minor reformatting
	Node returns Node_Or_Entity_Id (doc change only)

	* xgnatugn.adb: Replace ACADEMICEDITION with GPLEDITION

	* g-arrspl.ads (Create): Update comments.

	* sem.ads: Add details on the handling of the scope stack.

        * usage.adb: Update documentation.

	* validsw.ads, validsw.adb: 
	Add definition of Validity_Check_Components and implement -gnatVe/E

        * vms_data.ads: Add missing VMS qualifiers.

	* s-addope.ads: Add documentation on overflow and divide by zero

From-SVN: r118328
parent ab31b1a6
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 1992-2005, Free Software Foundation, Inc. --
-- Copyright (C) 1992-2006, 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- --
......@@ -104,8 +104,8 @@ package body Debug is
-- d.i
-- d.j
-- d.k
-- d.l
-- d.m
-- d.l Use Ada 95 semantics for limited function returns
-- d.m For -gnatl, print full source only for main unit
-- d.n
-- d.o
-- d.p
......@@ -115,11 +115,38 @@ package body Debug is
-- d.t
-- d.u
-- d.v
-- d.w
-- d.w Do not check for infinite while loops
-- d.x No exception handlers
-- d.y
-- d.z
-- d.A
-- d.B
-- d.C
-- d.D
-- d.E
-- d.F
-- d.G
-- d.H
-- d.I
-- d.J
-- d.K
-- d.L
-- d.M
-- d.N
-- d.O
-- d.P
-- d.Q
-- d.R
-- d.S
-- d.T
-- d.U
-- d.V
-- d.W
-- d.X
-- d.Y
-- d.Z
-- d1 Error msgs have node numbers where possible
-- d2 Eliminate error flags in verbose form error messages
-- d3 Dump bad node in Comperr on an abort
......@@ -133,7 +160,7 @@ package body Debug is
-- Debug flags for binder (GNATBIND)
-- da All links (including internal units) listed if there is a cycle
-- db
-- db Output information from Better_Choice
-- dc List units as they are chosen
-- dd
-- de Elaboration dependencies including system units
......@@ -146,7 +173,7 @@ package body Debug is
-- dl
-- dm
-- dn List details of manipulation of Num_Pred values
-- do
-- do Use old preference for elaboration order
-- dp
-- dq
-- dr
......@@ -403,6 +430,8 @@ package body Debug is
-- in preelaborable packages, but this restriction is a huge pain,
-- especially in the predefined library units.
-- dQ needs full documentation ???
-- dR Bypass the check for a proper version of s-rpc being present
-- to use the -gnatz? switch. This allows debugging of the use
-- of stubs generation without needing to have GLADE (or some
......@@ -445,6 +474,19 @@ package body Debug is
-- in seriously non-conforming behavior, but is useful sometimes
-- when tracking down handling of complex expressions.
-- d.l Use Ada 95 semantics for limited function returns. This may be
-- used to work around the incompatibility introduced by AI-318-2.
-- It is useful only in -gnat05 mode.
-- d.m When -gnatl is used, the normal output includes full listings of
-- all files in the extended main source (body/spec/subunits). If this
-- debug switch is used, then the full listing is given only for the
-- main source (this corresponds to a previous behavior of -gnatl and
-- is used for running the ACATS tests).
-- d.w This flag turns off the scanning of while loops to detect possible
-- infinite loops.
-- d.x No exception handlers in generated code. This causes exception
-- handlers to be eliminated from the generated code. They are still
-- fully compiled and analyzed, they just get eliminated from the
......@@ -519,6 +561,12 @@ package body Debug is
-- the algorithm used to determine a correct order of elaboration. This
-- is useful in diagnosing any problems in its behavior.
-- do Use old elaboration order preference. The new preference rules
-- prefer specs with no bodies to specs with bodies, and between two
-- specs with bodies, prefers the one whose body is closer to being
-- able to be elaborated. This is a clear improvement, but we provide
-- this debug flag in case of regressions.
-- du List unit name and file name for each unit as it is read in
-- dx Force the binder to read (and then ignore) the xref information
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 1992-2005, Free Software Foundation, Inc. --
-- Copyright (C) 1992-2006, 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- --
......@@ -86,7 +86,7 @@ package Elists is
function Elmts_Address return System.Address;
-- Return address of Elmts table (used in Back_End for Gigi call)
function Node (Elmt : Elmt_Id) return Node_Id;
function Node (Elmt : Elmt_Id) return Node_Or_Entity_Id;
pragma Inline (Node);
-- Returns the value of a given list element. Returns Empty if Elmt
-- is set to No_Elmt.
......@@ -98,13 +98,13 @@ package Elists is
function First_Elmt (List : Elist_Id) return Elmt_Id;
pragma Inline (First_Elmt);
-- Obtains the first element of the given element list or, if the
-- list has no items, then No_Elmt is returned.
-- Obtains the first element of the given element list or, if the list has
-- no items, then No_Elmt is returned.
function Last_Elmt (List : Elist_Id) return Elmt_Id;
pragma Inline (Last_Elmt);
-- Obtains the last element of the given element list or, if the
-- list has no items, then No_Elmt is returned.
-- Obtains the last element of the given element list or, if the list has
-- no items, then No_Elmt is returned.
function Next_Elmt (Elmt : Elmt_Id) return Elmt_Id;
pragma Inline (Next_Elmt);
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 2002-2005, Free Software Foundation, Inc. --
-- Copyright (C) 2002-2006, 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- --
......@@ -90,6 +90,10 @@ package GNAT.Array_Split is
-- is a sequence of Element along which to split the array. The source
-- array is sliced at separator boundaries. The separators are not
-- included as part of the resulting slices.
--
-- Note that if From is terminated by a separator an extra empty element
-- is added to the slice set. If From only contains a separator the slice
-- set contains two empty elements.
procedure Create
(S : out Slice_Set;
......
......@@ -712,7 +712,7 @@ alternative forms for the above spec are:
@item
Function and procedure bodies should usually be sorted alphabetically. Do
not attempt to sort them in some logical order by functionality. For a
sequence of subrpgroams specs, a general alphabetical sorting is also
sequence of subprogram specs, a general alphabetical sorting is also
usually appropriate, but occasionally it makes sense to group by major
function, with appropriate headers.
......@@ -749,7 +749,8 @@ A sequence of declarations may optionally be separated from the following
begin by a blank line. Just as we optionally allow blank lines in general
between declarations, this blank line should be present only if it improves
readability. Generally we avoid this blank line if the declarative part is
small (one or two lines) and we include it if the declarative part is long.
small (one or two lines) and the body has no blank lines, and we include it
if the declarative part is long or if the body has blank lines.
@item
If the declarations in a subprogram contain at least one nested
......@@ -766,8 +767,78 @@ subprogram, there is a comment line and a blank line:
@end group
@end smallexample
@item
When nested subprograms are present, variables that are referenced by any
nested subprogram should precede the nested subprogram specs. For variables
that are not referenced by nested procedures, the declarations can either also
be before any of the nested subprogram specs (this is the old style, more
generally used). Or then can come just before the begin, with a header. The
following example shows the two possible styles:
@smallexample @c adanocomment
@group
procedure Style1 is
Var_Referenced_In_Nested : Integer;
Var_Referenced_Only_In_Style1 : Integer;
proc Nested;
-- Comments ...
------------
-- Nested --
------------
procedure Nested is
begin
...
end Nested;
-- Start of processing for Style1
begin
...
end Style1;
@end group
@group
procedure Style2 is
Var_Referenced_In_Nested : Integer;
proc Nested;
-- Comments ...
------------
-- Nested --
------------
procedure Nested is
begin
...
end Nested;
-- Local variables
Var_Referenced_Only_In_Style2 : Integer;
-- Start of processing for Style2
begin
...
end Style2;
@end group
@end smallexample
@noindent
For new code, we generally prefer Style2, but we do not insist on
modifying all legacy occurrences of Style1, which is still much
more common in the sources.
@end itemize
@c -------------------------------------------------------------------------
@node Packages, Program Structure, Subprograms, Top
@section Packages and Visibility Rules
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 1992-2005, Free Software Foundation, Inc. --
-- Copyright (C) 1992-2006, 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- --
......@@ -269,12 +269,54 @@ package Sem is
-- Scope Stack --
-----------------
-- The scope stack holds all entries of the scope table. As in the parser,
-- we use Last as the stack pointer, so that we can always find the scope
-- that is currently open in Scope_Stack.Table (Scope_Stack.Last). The
-- oldest entry, at Scope_Stack (0) is Standard. The entries in the table
-- include the entity for the referenced scope, together with information
-- used to restore the proper setting of check suppressions on scope exit.
-- The scope stack indicates the declarative regions that are currently
-- being processed (analyzed and/or expanded). The scope stack is one of
-- basic visibility structures in the compiler: entities that are declared
-- in a scope that is currently on the scope stack are immediately visible.
-- (leaving aside issues of hiding and overloading).
-- Initially, the scope stack only contains an entry for package Standard.
-- When a compilation unit, subprogram unit, block or declarative region
-- is being processed, the corresponding entity is pushed on the scope
-- stack. It is removed after the processing step is completed. A given
-- entity can be placed several times on the scope stack, for example
-- when processing derived type declarations, freeze nodes, etc. The top
-- of the scope stack is the innermost scope currently being processed.
-- It is obtained through function Current_Scope. After a compilation unit
-- has been processed, the scope stack must contain only Standard.
-- The predicate In_Open_Scopes specifies whether a scope is currently
-- on the scope stack.
-- This model is complicated by the need to compile units on the fly, in
-- the middle of the compilation of other units. This arises when compiling
-- instantiations, and when compiling run-time packages obtained through
-- rtsfind. Given that the scope stack is a single static and global
-- structure (not originally designed for the recursive processing required
-- by rtsfind for example) additional machinery is needed to indicate what
-- is currently being compiled. As a result, the scope stack holds several
-- contiguous sections that correspond to the compilation of a given
-- compilation unit. These sections are separated by distinct occurrences
-- of package Standard. The currently active section of the scope stack
-- goes from the current scope to the first occurrence of Standard, which
-- is additionally marked with the flag Is_Active_Stack_Base. The basic
-- visibility routine (Find_Direct_Name, sem_ch8) uses this contiguous
-- section of the scope stack to determine whether a given entity is or
-- is not visible at a point. In_Open_Scopes only examines the currently
-- active section of the scope stack.
-- Similar complications arise when processing child instances. These
-- must be compiled in the context of parent instances, and therefore the
-- parents must be pushed on the stack before compiling the child, and
-- removed afterwards. Routines Save_Scope_Stack and Restore_Scope_Stack
-- are used to set/reset the visibility of entities declared in scopes
-- that are currently on the scope stack, and are used when compiling
-- instance bodies on the fly.
-- It is clear in retrospect that all semantic processing and visibility
-- structures should have been fully recursive. The rtsfind mechanism,
-- and the complexities brought about by subunits and by generic child
-- units and their instantitions, have led to a hybrid model that carries
-- more state than one would wish.
type Scope_Stack_Entry is record
Entity : Entity_Id;
......@@ -294,9 +336,12 @@ package Sem is
-- Marks Transient Scopes (See Exp_Ch7 body for details)
Previous_Visibility : Boolean;
-- Used when installing the parent (s) of the current compilation
-- unit. The parent may already be visible because of an ongoing
-- compilation, and the proper visibility must be restored on exit.
-- Used when installing the parent(s) of the current compilation unit.
-- The parent may already be visible because of an ongoing compilation,
-- and the proper visibility must be restored on exit. The flag is
-- typically needed when the context of a child unit requires
-- compilation of a sibling. In other cases the flag is set to False.
-- See Sem_Ch10 (Install_Parents, Remove_Parents).
Node_To_Be_Wrapped : Node_Id;
-- Only used in transient scopes. Records the node which will
......@@ -306,33 +351,33 @@ package Sem is
Actions_To_Be_Wrapped_After : List_Id;
-- Actions that have to be inserted at the start or at the end of a
-- transient block. Used to temporarily hold these actions until the
-- block is created, at which time the actions are moved to the
-- block.
-- block is created, at which time the actions are moved to the block.
Pending_Freeze_Actions : List_Id;
-- Used to collect freeze entity nodes and associated actions that
-- are generated in a inner context but need to be analyzed outside,
-- such as records and initialization procedures. On exit from the
-- scope, this list of actions is inserted before the scope construct
-- and analyzed to generate the corresponding freeze processing and
-- elaboration of other associated actions.
-- Used to collect freeze entity nodes and associated actions that are
-- generated in a inner context but need to be analyzed outside, such as
-- records and initialization procedures. On exit from the scope, this
-- list of actions is inserted before the scope construct and analyzed
-- to generate the corresponding freeze processing and elaboration of
-- other associated actions.
First_Use_Clause : Node_Id;
-- Head of list of Use_Clauses in current scope. The list is built
-- when the declarations in the scope are processed. The list is
-- traversed on scope exit to undo the effect of the use clauses.
-- Head of list of Use_Clauses in current scope. The list is built when
-- the declarations in the scope are processed. The list is traversed
-- on scope exit to undo the effect of the use clauses.
Component_Alignment_Default : Component_Alignment_Kind;
-- Component alignment to be applied to any record or array types
-- that are declared for which a specific component alignment pragma
-- does not set the alignment.
-- Component alignment to be applied to any record or array types that
-- are declared for which a specific component alignment pragma does not
-- set the alignment.
Is_Active_Stack_Base : Boolean;
-- Set to true only when entering the scope for Standard_Standard from
-- from within procedure Semantics. Indicates the base of the current
-- active set of scopes. Needed by In_Open_Scopes to handle cases
-- where Standard_Standard can be pushed in the middle of the active
-- set of scopes (occurs for instantiations of generic child units).
-- active set of scopes. Needed by In_Open_Scopes to handle cases where
-- Standard_Standard can be pushed anew on the scope stack to start a
-- new active section (see comment above).
end record;
package Scope_Stack is new Table.Table (
......
......@@ -56,6 +56,7 @@ gcc -c ^ GNAT COMPILE
-gnatdc ^ /TRACE_UNITS
-gnatdO ^ /REPORT_ERRORS=IMMEDIATE
-gnatC ^ /COMPRESS_NAMES
-gnatDG ^ /XDEBUG /EXPAND_SOURCEA
-gnatD ^ /XDEBUG
-gnatec ^ /CONFIGURATION_PRAGMAS_FILE
-gnateD ^ /SYMBOL_PREPROCESSING
......@@ -70,6 +71,10 @@ gcc -c ^ GNAT COMPILE
-gnatk ^ /FILE_NAME_MAX_LENGTH
-gnatl ^ /LIST
-gnatL ^ /LONGJMP_SETJMP
-gnatj ^ /JUSTIFY_MESSAGES
-gnatj0 ^ /NO_JUSTIFY_MESSAGES
-gnatjnn ^ /JUSTIFY_MESSAGES=nn
-gnatL ^ /INTERSPERSE_SOURCE
-gnatm ^ /ERROR_LIMIT
-gnatm2 ^ /ERROR_LIMIT=2
-gnatn ^ /INLINE=PRAGMA
......@@ -135,13 +140,19 @@ gcc -c ^ GNAT COMPILE
-gnatwO ^ /WARNINGS=NOOVERLAYS
-gnatwp ^ /WARNINGS=INEFFECTIVE_INLINE
-gnatwP ^ /WARNINGS=NOINEFFECTIVE_INLINE
-gnatwq ^ /WARNINGS=MISSING_PARENS
-gnatwQ ^ /WARNINGS=NOMISSING_PARENS
-gnatwr ^ /WARNINGS=REDUNDANT
-gnatwR ^ /WARNINGS=NOREDUNDANT
-gnatws ^ /WARNINGS=SUPPRESS
-gnatwt ^ /WARNINGS=DELETED_CODE
-gnatwT ^ /WARNINGS=NODELETED_CODE
-gnatwu ^ /WARNINGS=UNUSED
-gnatwU ^ /WARNINGS=NOUNUSED
-gnatwv ^ /WARNINGS=VARIABLES_UNINITIALIZED
-gnatwV ^ /WARNINGS=NOVARIABLES_UNINITIALIZED
-gnatww ^ /WARNINGS=LOWBOUND_ASSUMED
-gnatwW ^ /WARNINGS=NOLOWBOUND_ASSUMED
-gnatwx ^ /WARNINGS=IMPORT_EXPORT_PRAGMAS
-gnatwX ^ /WARNINGS=NOIMPORT_EXPORT_PRAGMAS
-gnatwy ^ /WARNINGS=ADA_2005_COMPATIBILITY
......
......@@ -210,15 +210,27 @@ begin
Write_Switch_Char ("i?");
Write_Line ("Identifier char set (?=1/2/3/4/5/8/9/p/f/n/w)");
-- Line for -gnatj switch
Write_Switch_Char ("jnn");
Write_Line ("Format error and warning messages to fit nn character lines");
-- Line for -gnatk switch
Write_Switch_Char ("k");
Write_Line ("Limit file names to nn characters (k = krunch)");
-- Line for -gnatl switch
-- Lines for -gnatl switch
Write_Switch_Char ("l");
Write_Line ("Output full source listing with embedded error messages");
Write_Switch_Char ("l=f");
Write_Line ("Output full source listing to specified file");
-- Line for -gnatL switch
Write_Switch_Char ("L");
Write_Line ("List corresponding source text in -gnatG or -gnatD output");
-- Line for -gnatm switch
......@@ -317,6 +329,8 @@ begin
Write_Line (" C turn off checking for copies");
Write_Line (" d turn on default (RM) checking");
Write_Line (" D turn off default (RM) checking");
Write_Line (" e turn on checking for elementary components");
Write_Line (" E turn off checking for elementary components");
Write_Line (" f turn on checking for floating-point");
Write_Line (" F turn off checking for floating-point");
Write_Line (" i turn on checking for in params");
......@@ -339,7 +353,7 @@ begin
Write_Switch_Char ("wxx");
Write_Line ("Enable selected warning modes, xx = list of parameters:");
Write_Line (" a turn on all optional warnings (except d,h,l)");
Write_Line (" a turn on all optional warnings (except d,h,l,t)");
Write_Line (" A turn off all optional warnings");
Write_Line (" b turn on warnings for bad fixed value " &
"(not multiple of small)");
......@@ -377,13 +391,22 @@ begin
Write_Line (" O turn off warnings for address clause overlay");
Write_Line (" p turn on warnings for ineffective pragma Inline");
Write_Line (" P* turn off warnings for ineffective pragma Inline");
Write_Line (" q turn on warnings for questionable " &
"missing paretheses");
Write_Line (" Q* turn off warnings for questionable " &
"missing paretheses");
Write_Line (" r turn on warnings for redundant construct");
Write_Line (" R* turn off warnings for redundant construct");
Write_Line (" s suppress all warnings");
Write_Line (" t turn on warnings for tracking deleted code");
Write_Line (" T* turn off warnings for tracking deleted code");
Write_Line (" u turn on warnings for unused entity");
Write_Line (" U* turn off warnings for unused entity");
Write_Line (" v* turn on warnings for unassigned variable");
Write_Line (" V turn off warnings for unassigned variable");
Write_Line (" w* turn on warnings for wrong low bound assumption");
Write_Line (" W turn off warnings for wrong low bound " &
"assumption");
Write_Line (" x* turn on warnings for export/import");
Write_Line (" X turn off warnings for export/import");
Write_Line (" y* turn on warnings for Ada 2005 incompatibility");
......
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 2001-2003 Free Software Foundation, Inc. --
-- Copyright (C) 2001-2006, 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- --
......@@ -34,6 +34,7 @@ package body Validsw is
procedure Reset_Validity_Check_Options is
begin
Validity_Check_Components := False;
Validity_Check_Copies := False;
Validity_Check_Default := True;
Validity_Check_Floating_Point := False;
......@@ -75,6 +76,7 @@ package body Validsw is
Add ('n', not Validity_Check_Default);
Add ('c', Validity_Check_Copies);
Add ('e', Validity_Check_Components);
Add ('f', Validity_Check_Floating_Point);
Add ('i', Validity_Check_In_Params);
Add ('m', Validity_Check_In_Out_Params);
......@@ -136,6 +138,9 @@ package body Validsw is
when 'd' =>
Validity_Check_Default := True;
when 'e' =>
Validity_Check_Components := True;
when 'f' =>
Validity_Check_Floating_Point := True;
......@@ -166,6 +171,9 @@ package body Validsw is
when 'D' =>
Validity_Check_Default := False;
when 'E' =>
Validity_Check_Components := False;
when 'I' =>
Validity_Check_In_Params := False;
......@@ -191,6 +199,7 @@ package body Validsw is
Validity_Check_Tests := False;
when 'a' =>
Validity_Check_Components := True;
Validity_Check_Copies := True;
Validity_Check_Default := True;
Validity_Check_Floating_Point := True;
......@@ -203,6 +212,7 @@ package body Validsw is
Validity_Check_Tests := True;
when 'n' =>
Validity_Check_Components := False;
Validity_Check_Copies := False;
Validity_Check_Default := False;
Validity_Check_Floating_Point := False;
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 2001-2005, Free Software Foundation, Inc. --
-- Copyright (C) 2001-2006, 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- --
......@@ -47,6 +47,12 @@ package Validsw is
-- pragma, then the right side of assignments and also initializing
-- expressions in object declarations are checked for validity.
Validity_Check_Components : Boolean := False;
-- Controls validity checking for assignment to elementary components of
-- records. If this switch is set true using -gnatVe, or an 'e' in the
-- argument of Validity_Checks pragma, then the right hand of an assignment
-- to such a component is checked for validity.
Validity_Check_Default : Boolean := True;
-- Controls default (reference manual) validity checking. If this switch is
-- set to True using -gnatVd or a 'd' in the argument of a Validity_ Checks
......
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 2003-2005, Free Software Foundation, Inc. --
-- Copyright (C) 2003-2006, 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- --
......@@ -90,7 +90,7 @@
-- this is because we have menu problems if we let makeinfo handle
-- these ifset/ifclear pairs.
-- Note: @ifset/@ifclear commands for the edition flags (FSFEDITION,
-- PROEDITION, ACADEMICEDITION) are passed through unchanged
-- PROEDITION, GPLEDITION) are passed through unchanged
with Ada.Command_Line; use Ada.Command_Line;
with Ada.Strings; use Ada.Strings;
......@@ -161,21 +161,21 @@ procedure Xgnatugn is
-- It contains the Texinfo source code. Process_Source_File
-- performs the necessary replacements.
type Flag_Type is (UNW, VMS, FSFEDITION, PROEDITION, ACADEMICEDITION);
type Flag_Type is (UNW, VMS, FSFEDITION, PROEDITION, GPLEDITION);
-- The flags permitted in @ifset or @ifclear commands:
--
-- Targets for preprocessing
-- UNW (Unix and Windows) or VMS
--
-- Editions of the manual
-- FSFEDITION, PROEDITION, or ACADEMICEDITION
-- FSFEDITION, PROEDITION, or GPLEDITION
--
-- Conditional commands for target are processed by xgnatugn
--
-- Conditional commands for edition are passed through unchanged
subtype Target_Type is Flag_Type range UNW .. VMS;
subtype Edition_Type is Flag_Type range FSFEDITION .. ACADEMICEDITION;
subtype Edition_Type is Flag_Type range FSFEDITION .. GPLEDITION;
Target : Target_Type;
-- The Target variable is initialized using the command line
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment