4.3.3 Warning Message Control

In addition to error messages, which correspond to illegalities as defined in the Ada Reference Manual, the compiler detects two kinds of warning situations.

First, the compiler considers some constructs suspicious and generates a warning message to alert you to a possible error. Second, if the compiler detects a situation that is sure to raise an exception at run time, it generates a warning message. The following shows an example of warning messages:

e.adb:4:24: warning: creation of object may raise Storage_Error
e.adb:10:17: warning: static value out of range
e.adb:10:17: warning: "Constraint_Error" will be raised at run time

GNAT considers a large number of situations as appropriate for the generation of warning messages. As always, warnings are not definite indications of errors. For example, if you do an out-of-range assignment with the deliberate intention of raising a Constraint_Error exception, then the warning that may be issued does not indicate an error. Some of the situations for which GNAT issues warnings (at least some of the time) are given in the following list. This list is not complete, and new warnings are often added to subsequent versions of GNAT. The list is intended to give a general idea of the kinds of warnings that are generated.

The following section lists compiler switches that are available to control the handling of warning messages. It is also possible to exercise much finer control over what warnings are issued and suppressed using the GNAT pragma Warnings (see the description of the pragma in the GNAT_Reference_manual).

-gnatwa

‘Activate most optional warnings.’

This switch activates most optional warning messages. See the remaining list in this section for details on optional warning messages that can be individually controlled. The warnings that are not turned on by this switch are:

  • -gnatwd (implicit dereferencing)
  • -gnatw.d (tag warnings with -gnatw switch)
  • -gnatwh (hiding)
  • -gnatw.h (holes in record layouts)
  • -gnatw.j (late primitives of tagged types)
  • -gnatw.k (redefinition of names in standard)
  • -gnatwl (elaboration warnings)
  • -gnatw.l (inherited aspects)
  • -gnatw.n (atomic synchronization)
  • -gnatwo (address clause overlay)
  • -gnatw.o (values set by out parameters ignored)
  • -gnatw.q (questionable layout of record types)
  • -gnatw_q (ignored equality)
  • -gnatw_r (out-of-order record representation clauses)
  • -gnatw.s (overridden size clause)
  • -gnatw_s (ineffective predicate test)
  • -gnatwt (tracking of deleted conditional code)
  • -gnatw.u (unordered enumeration)
  • -gnatw.w (use of Warnings Off)
  • -gnatw.y (reasons for package needing body)

All other optional warnings are turned on.

-gnatwA

‘Suppress all optional errors.’

This switch suppresses all optional warning messages, see remaining list in this section for details on optional warning messages that can be individually controlled. Note that unlike switch -gnatws, the use of switch -gnatwA does not suppress warnings that are normally given unconditionally and cannot be individually controlled (for example, the warning about a missing exit path in a function). Also, again unlike switch -gnatws, warnings suppressed by the use of switch -gnatwA can be individually turned back on. For example the use of switch -gnatwA followed by switch -gnatwd will suppress all optional warnings except the warnings for implicit dereferencing.

-gnatw.a

‘Activate warnings on failing assertions.’

This switch activates warnings for assertions where the compiler can tell at compile time that the assertion will fail. Note that this warning is given even if assertions are disabled. The default is that such warnings are generated.

-gnatw.A

‘Suppress warnings on failing assertions.’

This switch suppresses warnings for assertions where the compiler can tell at compile time that the assertion will fail.

-gnatw_a

‘Activate warnings on anonymous allocators.’

This switch activates warnings for allocators of anonymous access types, which can involve run-time accessibility checks and lead to unexpected accessibility violations. For more details on the rules involved, see RM 3.10.2 (14).

-gnatw_A

‘Suppress warnings on anonymous allocators.’

This switch suppresses warnings for anonymous access type allocators.

-gnatwb

‘Activate warnings on bad fixed values.’

This switch activates warnings for static fixed-point expressions whose value is not an exact multiple of Small. Such values are implementation dependent, since an implementation is free to choose either of the multiples that surround the value. GNAT always chooses the closer one, but this is not required behavior, and it is better to specify a value that is an exact multiple, ensuring predictable execution. The default is that such warnings are not generated.

-gnatwB

‘Suppress warnings on bad fixed values.’

This switch suppresses warnings for static fixed-point expressions whose value is not an exact multiple of Small.

-gnatw.b

‘Activate warnings on biased representation.’

This switch activates warnings when a size clause, value size clause, component clause, or component size clause forces the use of biased representation for an integer type (e.g. representing a range of 10..11 in a single bit by using 0/1 to represent 10/11). The default is that such warnings are generated.

-gnatw.B

‘Suppress warnings on biased representation.’

This switch suppresses warnings for representation clauses that force the use of biased representation.

-gnatwc

‘Activate warnings on conditionals.’

This switch activates warnings for boolean expressions that are known to be True or False at compile time. The default is that such warnings are not generated. Note that this warning does not get issued for the use of boolean constants whose values are known at compile time, since this is a standard technique for conditional compilation in Ada, and this would generate too many false positive warnings.

This warning option also activates a special test for comparisons using the operators ‘>=’ and’ <=’. If the compiler can tell that only the equality condition is possible, then it will warn that the ‘>’ or ‘<’ part of the test is useless and that the operator could be replaced by ‘=’. An example would be comparing a Natural variable <= 0.

This warning option also generates warnings if one or both tests is optimized away in a membership test for integer values if the result can be determined at compile time. Range tests on enumeration types are not included, since it is common for such tests to include an end point.

This warning can also be turned on using -gnatwa.

-gnatwC

‘Suppress warnings on conditionals.’

This switch suppresses warnings for conditional expressions used in tests that are known to be True or False at compile time.

-gnatw.c

‘Activate warnings on missing component clauses.’

This switch activates warnings for record components where a record representation clause is present and has component clauses for the majority, but not all, of the components. A warning is given for each component for which no component clause is present.

-gnatw.C

‘Suppress warnings on missing component clauses.’

This switch suppresses warnings for record components that are missing a component clause in the situation described above.

-gnatw_c

‘Activate warnings on unknown condition in Compile_Time_Warning.’

This switch activates warnings on a pragma Compile_Time_Warning or Compile_Time_Error whose condition has a value that is not known at compile time. The default is that such warnings are generated.

-gnatw_C

‘Suppress warnings on unknown condition in Compile_Time_Warning.’

This switch suppresses warnings on a pragma Compile_Time_Warning or Compile_Time_Error whose condition has a value that is not known at compile time.

-gnatwd

‘Activate warnings on implicit dereferencing.’

If this switch is set, then the use of a prefix of an access type in an indexed component, slice, or selected component without an explicit .all will generate a warning. With this warning enabled, access checks occur only at points where an explicit .all appears in the source code (assuming no warnings are generated as a result of this switch). The default is that such warnings are not generated.

-gnatwD

‘Suppress warnings on implicit dereferencing.’

This switch suppresses warnings for implicit dereferences in indexed components, slices, and selected components.

-gnatw.d

‘Activate tagging of warning and info messages.’

If this switch is set, then warning messages are tagged, with one of the following strings:

  • ‘[-gnatw?]’ Used to tag warnings controlled by the switch -gnatwx where x is a letter a-z.
  • ‘[-gnatw.?]’ Used to tag warnings controlled by the switch -gnatw.x where x is a letter a-z.
  • ‘[-gnatel]’ Used to tag elaboration information (info) messages generated when the static model of elaboration is used and the -gnatel switch is set.
  • ‘[restriction warning]’ Used to tag warning messages for restriction violations, activated by use of the pragma Restriction_Warnings.
  • ‘[warning-as-error]’ Used to tag warning messages that have been converted to error messages by use of the pragma Warning_As_Error. Note that such warnings are prefixed by the string “error: ” rather than “warning: “.
  • ‘[enabled by default]’ Used to tag all other warnings that are always given by default, unless warnings are completely suppressed using pragma ‘Warnings(Off)’ or the switch -gnatws.
-gnatw.D

‘Deactivate tagging of warning and info messages messages.’

If this switch is set, then warning messages return to the default mode in which warnings and info messages are not tagged as described above for -gnatw.d.

-gnatwe

‘Treat warnings and style checks as errors.’

This switch causes warning messages and style check messages to be treated as errors. The warning string still appears, but the warning messages are counted as errors, and prevent the generation of an object file. Note that this is the only -gnatw switch that affects the handling of style check messages. Note also that this switch has no effect on info (information) messages, which are not treated as errors if this switch is present.

-gnatw.e

‘Activate every optional warning.’

This switch activates all optional warnings, including those which are not activated by -gnatwa. The use of this switch is not recommended for normal use. If you turn this switch on, it is almost certain that you will get large numbers of useless warnings. The warnings that are excluded from -gnatwa are typically highly specialized warnings that are suitable for use only in code that has been specifically designed according to specialized coding rules.

-gnatwE

‘Treat all run-time exception warnings as errors.’

This switch causes warning messages regarding errors that will be raised during run-time execution to be treated as errors.

-gnatwf

‘Activate warnings on unreferenced formals.’

This switch causes a warning to be generated if a formal parameter is not referenced in the body of the subprogram. This warning can also be turned on using -gnatwu. The default is that these warnings are not generated.

-gnatwF

‘Suppress warnings on unreferenced formals.’

This switch suppresses warnings for unreferenced formal parameters. Note that the combination -gnatwu followed by -gnatwF has the effect of warning on unreferenced entities other than subprogram formals.

-gnatwg

‘Activate warnings on unrecognized pragmas.’

This switch causes a warning to be generated if an unrecognized pragma is encountered. Apart from issuing this warning, the pragma is ignored and has no effect. The default is that such warnings are issued (satisfying the Ada Reference Manual requirement that such warnings appear).

-gnatwG

‘Suppress warnings on unrecognized pragmas.’

This switch suppresses warnings for unrecognized pragmas.

-gnatw.g

‘Warnings used for GNAT sources.’

This switch sets the warning categories that are used by the standard GNAT style. Currently this is equivalent to -gnatwAao.q.s.CI.V.X.Z but more warnings may be added in the future without advanced notice.

-gnatwh

‘Activate warnings on hiding.’

This switch activates warnings on hiding declarations that are considered potentially confusing. Not all cases of hiding cause warnings; for example an overriding declaration hides an implicit declaration, which is just normal code. The default is that warnings on hiding are not generated.

-gnatwH

‘Suppress warnings on hiding.’

This switch suppresses warnings on hiding declarations.

-gnatw.h

‘Activate warnings on holes/gaps in records.’

This switch activates warnings on component clauses in record representation clauses that leave holes (gaps) in the record layout. If a record representation clause does not specify a location for every component of the record type, then the warnings generated (or not generated) are unspecified. For example, there may be gaps for which either no warning is generated or a warning is generated that incorrectly describes the location of the gap. This undesirable situation can sometimes be avoided by adding (and specifying the location for) unused fill fields.

-gnatw.H

‘Suppress warnings on holes/gaps in records.’

This switch suppresses warnings on component clauses in record representation clauses that leave holes (haps) in the record layout.

-gnatwi

‘Activate warnings on implementation units.’

This switch activates warnings for a ‘with’ of an internal GNAT implementation unit, defined as any unit from the Ada, Interfaces, GNAT, or System hierarchies that is not documented in either the Ada Reference Manual or the GNAT Programmer’s Reference Manual. Such units are intended only for internal implementation purposes and should not be ‘with’ed by user programs. The default is that such warnings are generated

-gnatwI

‘Disable warnings on implementation units.’

This switch disables warnings for a ‘with’ of an internal GNAT implementation unit.

-gnatw.i

‘Activate warnings on overlapping actuals.’

This switch enables a warning on statically detectable overlapping actuals in a subprogram call, when one of the actuals is an in-out parameter, and the types of the actuals are not by-copy types. This warning is off by default.

-gnatw.I

‘Disable warnings on overlapping actuals.’

This switch disables warnings on overlapping actuals in a call.

-gnatwj

‘Activate warnings on obsolescent features (Annex J).’

If this warning option is activated, then warnings are generated for calls to subprograms marked with pragma Obsolescent and for use of features in Annex J of the Ada Reference Manual. In the case of Annex J, not all features are flagged. In particular, uses of package ASCII are not flagged, since these are very common and would generate many annoying positive warnings. The default is that such warnings are not generated.

In addition to the above cases, warnings are also generated for GNAT features that have been provided in past versions but which have been superseded (typically by features in the new Ada standard). For example, pragma Ravenscar will be flagged since its function is replaced by pragma Profile(Ravenscar), and pragma Interface_Name will be flagged since its function is replaced by pragma Import.

Note that this warning option functions differently from the restriction No_Obsolescent_Features in two respects. First, the restriction applies only to annex J features. Second, the restriction does flag uses of package ASCII.

-gnatwJ

‘Suppress warnings on obsolescent features (Annex J).’

This switch disables warnings on use of obsolescent features.

-gnatw.j

‘Activate warnings on late declarations of tagged type primitives.’

This switch activates warnings on visible primitives added to a tagged type after deriving a private extension from it.

-gnatw.J

‘Suppress warnings on late declarations of tagged type primitives.’

This switch suppresses warnings on visible primitives added to a tagged type after deriving a private extension from it.

-gnatwk

‘Activate warnings on variables that could be constants.’

This switch activates warnings for variables that are initialized but never modified, and then could be declared constants. The default is that such warnings are not given.

-gnatwK

‘Suppress warnings on variables that could be constants.’

This switch disables warnings on variables that could be declared constants.

-gnatw.k

‘Activate warnings on redefinition of names in standard.’

This switch activates warnings for declarations that declare a name that is defined in package Standard. Such declarations can be confusing, especially since the names in package Standard continue to be directly visible, meaning that use visibility on such redeclared names does not work as expected. Names of discriminants and components in records are not included in this check.

-gnatw.K

‘Suppress warnings on redefinition of names in standard.’

This switch disables warnings for declarations that declare a name that is defined in package Standard.

-gnatwl

‘Activate warnings for elaboration pragmas.’

This switch activates warnings for possible elaboration problems, including suspicious use of Elaborate pragmas, when using the static elaboration model, and possible situations that may raise Program_Error when using the dynamic elaboration model. See the section in this guide on elaboration checking for further details. The default is that such warnings are not generated.

-gnatwL

‘Suppress warnings for elaboration pragmas.’

This switch suppresses warnings for possible elaboration problems.

-gnatw.l

‘List inherited aspects as info messages.’

This switch causes the compiler to list inherited invariants, preconditions, and postconditions from Type_Invariant’Class, Invariant’Class, Pre’Class, and Post’Class aspects. Also list inherited subtype predicates.

-gnatw.L

‘Suppress listing of inherited aspects as info messages.’

This switch suppresses listing of inherited aspects.

-gnatwm

‘Activate warnings on modified but unreferenced variables.’

This switch activates warnings for variables that are assigned (using an initialization value or with one or more assignment statements) but whose value is never read. The warning is suppressed for volatile variables and also for variables that are renamings of other variables or for which an address clause is given. The default is that these warnings are not given.

-gnatwM

‘Disable warnings on modified but unreferenced variables.’

This switch disables warnings for variables that are assigned or initialized, but never read.

-gnatw.m

‘Activate warnings on suspicious modulus values.’

This switch activates warnings for modulus values that seem suspicious. The cases caught are where the size is the same as the modulus (e.g. a modulus of 7 with a size of 7 bits), and modulus values of 32 or 64 with no size clause. The guess in both cases is that 2**x was intended rather than x. In addition expressions of the form 2*x for small x generate a warning (the almost certainly accurate guess being that 2**x was intended). This switch also activates warnings for negative literal values of a modular type, which are interpreted as large positive integers after wrap-around. The default is that these warnings are given.

-gnatw.M

‘Disable warnings on suspicious modulus values.’

This switch disables warnings for suspicious modulus values.

-gnatwn

‘Set normal warnings mode.’

This switch sets normal warning mode, in which enabled warnings are issued and treated as warnings rather than errors. This is the default mode. the switch -gnatwn can be used to cancel the effect of an explicit -gnatws or -gnatwe. It also cancels the effect of the implicit -gnatwe that is activated by the use of -gnatg.

-gnatw.n

‘Activate warnings on atomic synchronization.’

This switch activates warnings when an access to an atomic variable requires the generation of atomic synchronization code. These warnings are off by default.

-gnatw.N

‘Suppress warnings on atomic synchronization.’

This switch suppresses warnings when an access to an atomic variable requires the generation of atomic synchronization code.

-gnatwo

‘Activate warnings on address clause overlays.’

This switch activates warnings for possibly unintended initialization effects of defining address clauses that cause one variable to overlap another. The default is that such warnings are generated.

-gnatwO

‘Suppress warnings on address clause overlays.’

This switch suppresses warnings on possibly unintended initialization effects of defining address clauses that cause one variable to overlap another.

-gnatw.o

‘Activate warnings on modified but unreferenced out parameters.’

This switch activates warnings for variables that are modified by using them as actuals for a call to a procedure with an out mode formal, where the resulting assigned value is never read. It is applicable in the case where there is more than one out mode formal. If there is only one out mode formal, the warning is issued by default (controlled by -gnatwu). The warning is suppressed for volatile variables and also for variables that are renamings of other variables or for which an address clause is given. The default is that these warnings are not given.

-gnatw.O

‘Disable warnings on modified but unreferenced out parameters.’

This switch suppresses warnings for variables that are modified by using them as actuals for a call to a procedure with an out mode formal, where the resulting assigned value is never read.

-gnatwp

‘Activate warnings on ineffective pragma Inlines.’

This switch activates warnings for failure of front end inlining (activated by -gnatN) to inline a particular call. There are many reasons for not being able to inline a call, including most commonly that the call is too complex to inline. The default is that such warnings are not given. Warnings on ineffective inlining by the gcc back-end can be activated separately, using the gcc switch -Winline.

-gnatwP

‘Suppress warnings on ineffective pragma Inlines.’

This switch suppresses warnings on ineffective pragma Inlines. If the inlining mechanism cannot inline a call, it will simply ignore the request silently.

-gnatw.p

‘Activate warnings on parameter ordering.’

This switch activates warnings for cases of suspicious parameter ordering when the list of arguments are all simple identifiers that match the names of the formals, but are in a different order. The warning is suppressed if any use of named parameter notation is used, so this is the appropriate way to suppress a false positive (and serves to emphasize that the “misordering” is deliberate). The default is that such warnings are not given.

-gnatw.P

‘Suppress warnings on parameter ordering.’

This switch suppresses warnings on cases of suspicious parameter ordering.

-gnatw_p

‘Activate warnings for pedantic checks.’

This switch activates warnings for the failure of certain pedantic checks. The only case currently supported is a check that the subtype_marks given for corresponding formal parameter and function results in a subprogram declaration and its body denote the same subtype declaration. The default is that such warnings are not given.

-gnatw_P

‘Suppress warnings for pedantic checks.’

This switch suppresses warnings on violations of pedantic checks.

-gnatwq

‘Activate warnings on questionable missing parentheses.’

This switch activates warnings for cases where parentheses are not used and the result is potential ambiguity from a readers point of view. For example (not a > b) when a and b are modular means ((not a) > b) and very likely the programmer intended (not (a > b)). Similarly (-x mod 5) means (-(x mod 5)) and quite likely ((-x) mod 5) was intended. In such situations it seems best to follow the rule of always parenthesizing to make the association clear, and this warning switch warns if such parentheses are not present. The default is that these warnings are given.

-gnatwQ

‘Suppress warnings on questionable missing parentheses.’

This switch suppresses warnings for cases where the association is not clear and the use of parentheses is preferred.

-gnatw.q

‘Activate warnings on questionable layout of record types.’

This switch activates warnings for cases where the default layout of a record type, that is to say the layout of its components in textual order of the source code, would very likely cause inefficiencies in the code generated by the compiler, both in terms of space and speed during execution. One warning is issued for each problematic component without representation clause in the nonvariant part and then in each variant recursively, if any.

The purpose of these warnings is neither to prescribe an optimal layout nor to force the use of representation clauses, but rather to get rid of the most blatant inefficiencies in the layout. Therefore, the default layout is matched against the following synthetic ordered layout and the deviations are flagged on a component-by-component basis:

  • first all components or groups of components whose length is fixed and a multiple of the storage unit,
  • then the remaining components whose length is fixed and not a multiple of the storage unit,
  • then the remaining components whose length doesn’t depend on discriminants (that is to say, with variable but uniform length for all objects),
  • then all components whose length depends on discriminants,
  • finally the variant part (if any),

for the nonvariant part and for each variant recursively, if any.

The exact wording of the warning depends on whether the compiler is allowed to reorder the components in the record type or precluded from doing it by means of pragma No_Component_Reordering.

The default is that these warnings are not given.

-gnatw.Q

‘Suppress warnings on questionable layout of record types.’

This switch suppresses warnings for cases where the default layout of a record type would very likely cause inefficiencies.

-gnatw_q

‘Activate warnings for ignored equality operators.’

This switch activates warnings for a user-defined “=” function that does not compose (i.e. is ignored for a predefined “=” for a composite type containing a component whose type has the user-defined “=” as primitive). Note that the user-defined “=” must be a primitive operator in order to trigger the warning. See RM-4.5.2(14/3-15/5, 21, 24/3, 32.1/1) for the exact Ada rules on composability of “=”.

The default is that these warnings are not given.

-gnatw_Q

‘Suppress warnings for ignored equality operators.’

-gnatwr

‘Activate warnings on redundant constructs.’

This switch activates warnings for redundant constructs. The following is the current list of constructs regarded as redundant:

  • Assignment of an item to itself.
  • Type conversion that converts an expression to its own type.
  • Use of the attribute Base where typ'Base is the same as typ.
  • Use of pragma Pack when all components are placed by a record representation clause.
  • Exception handler containing only a reraise statement (raise with no operand) which has no effect.
  • Use of the operator abs on an operand that is known at compile time to be non-negative
  • Comparison of an object or (unary or binary) operation of boolean type to an explicit True value.
  • Import of parent package.

The default is that warnings for redundant constructs are not given.

-gnatwR

‘Suppress warnings on redundant constructs.’

This switch suppresses warnings for redundant constructs.

-gnatw.r

‘Activate warnings for object renaming function.’

This switch activates warnings for an object renaming that renames a function call, which is equivalent to a constant declaration (as opposed to renaming the function itself). The default is that these warnings are given.

-gnatw.R

‘Suppress warnings for object renaming function.’

This switch suppresses warnings for object renaming function.

-gnatw_r

‘Activate warnings for out-of-order record representation clauses.’

This switch activates warnings for record representation clauses, if the order of component declarations, component clauses, and bit-level layout do not all agree. The default is that these warnings are not given.

-gnatw_R

‘Suppress warnings for out-of-order record representation clauses.’

-gnatws

‘Suppress all warnings.’

This switch completely suppresses the output of all warning messages from the GNAT front end, including both warnings that can be controlled by switches described in this section, and those that are normally given unconditionally. The effect of this suppress action can only be cancelled by a subsequent use of the switch -gnatwn.

Note that switch -gnatws does not suppress warnings from the gcc back end. To suppress these back end warnings as well, use the switch -w in addition to -gnatws. Also this switch has no effect on the handling of style check messages.

-gnatw.s

‘Activate warnings on overridden size clauses.’

This switch activates warnings on component clauses in record representation clauses where the length given overrides that specified by an explicit size clause for the component type. A warning is similarly given in the array case if a specified component size overrides an explicit size clause for the array component type.

-gnatw.S

‘Suppress warnings on overridden size clauses.’

This switch suppresses warnings on component clauses in record representation clauses that override size clauses, and similar warnings when an array component size overrides a size clause.

-gnatw_s

‘Activate warnings on ineffective predicate tests.’

This switch activates warnings on Static_Predicate aspect specifications that test for values that do not belong to the parent subtype. Not all such ineffective tests are detected.

-gnatw_S

‘Suppress warnings on ineffective predicate tests.’

This switch suppresses warnings on Static_Predicate aspect specifications that test for values that do not belong to the parent subtype.

-gnatwt

‘Activate warnings for tracking of deleted conditional code.’

This switch activates warnings for tracking of code in conditionals (IF and CASE statements) that is detected to be dead code which cannot be executed, and which is removed by the front end. This warning is off by default. This may be useful for detecting deactivated code in certified applications.

-gnatwT

‘Suppress warnings for tracking of deleted conditional code.’

This switch suppresses warnings for tracking of deleted conditional code.

-gnatw.t

‘Activate warnings on suspicious contracts.’

This switch activates warnings on suspicious contracts. This includes warnings on suspicious postconditions (whether a pragma Postcondition or a Post aspect in Ada 2012) and suspicious contract cases (pragma or aspect Contract_Cases). A function postcondition or contract case is suspicious when no postcondition or contract case for this function mentions the result of the function. A procedure postcondition or contract case is suspicious when it only refers to the pre-state of the procedure, because in that case it should rather be expressed as a precondition. This switch also controls warnings on suspicious cases of expressions typically found in contracts like quantified expressions and uses of Update attribute. The default is that such warnings are generated.

-gnatw.T

‘Suppress warnings on suspicious contracts.’

This switch suppresses warnings on suspicious contracts.

-gnatwu

‘Activate warnings on unused entities.’

This switch activates warnings to be generated for entities that are declared but not referenced, and for units that are ‘with’ed and not referenced. In the case of packages, a warning is also generated if no entities in the package are referenced. This means that if a with’ed package is referenced but the only references are in use clauses or renames declarations, a warning is still generated. A warning is also generated for a generic package that is ‘with’ed but never instantiated. In the case where a package or subprogram body is compiled, and there is a ‘with’ on the corresponding spec that is only referenced in the body, a warning is also generated, noting that the ‘with’ can be moved to the body. The default is that such warnings are not generated. This switch also activates warnings on unreferenced formals (it includes the effect of -gnatwf).

-gnatwU

‘Suppress warnings on unused entities.’

This switch suppresses warnings for unused entities and packages. It also turns off warnings on unreferenced formals (and thus includes the effect of -gnatwF).

-gnatw.u

‘Activate warnings on unordered enumeration types.’

This switch causes enumeration types to be considered as conceptually unordered, unless an explicit pragma Ordered is given for the type. The effect is to generate warnings in clients that use explicit comparisons or subranges, since these constructs both treat objects of the type as ordered. (A ‘client’ is defined as a unit that is other than the unit in which the type is declared, or its body or subunits.) Please refer to the description of pragma Ordered in the GNAT Reference Manual for further details. The default is that such warnings are not generated.

-gnatw.U

‘Deactivate warnings on unordered enumeration types.’

This switch causes all enumeration types to be considered as ordered, so that no warnings are given for comparisons or subranges for any type.

-gnatwv

‘Activate warnings on unassigned variables.’

This switch activates warnings for access to variables which may not be properly initialized. The default is that such warnings are generated. This switch will also be emitted when initializing an array or record object via the following aggregate:

Array_Or_Record : XXX := (others => <>);

unless the relevant type fully initializes all components.

-gnatwV

‘Suppress warnings on unassigned variables.’

This switch suppresses warnings for access to variables which may not be properly initialized.

-gnatw.v

‘Activate warnings for non-default bit order.’

This switch activates warning messages about the effects of non-default bit-order on records to which a component clause is applied. The effect of specifying non-default bit ordering is a bit subtle (and changed with Ada 2005), so these messages, which are given by default, are useful in understanding the exact consequences of using this feature.

-gnatw.V

‘Suppress warnings for non-default bit order.’

This switch suppresses warnings for the effects of specifying non-default bit order on record components with component clauses.

-gnatww

‘Activate warnings on wrong low bound assumption.’

This switch activates warnings for indexing an unconstrained string parameter with a literal or S’Length. This is a case where the code is assuming that the low bound is one, which is in general not true (for example when a slice is passed). The default is that such warnings are generated.

-gnatwW

‘Suppress warnings on wrong low bound assumption.’

This switch suppresses warnings for indexing an unconstrained string parameter with a literal or S’Length. Note that this warning can also be suppressed in a particular case by adding an assertion that the lower bound is 1, as shown in the following example:

procedure K (S : String) is
   pragma Assert (S'First = 1);
   ...
-gnatw.w

‘Activate warnings on Warnings Off pragmas.’

This switch activates warnings for use of pragma Warnings (Off, entity) where either the pragma is entirely useless (because it suppresses no warnings), or it could be replaced by pragma Unreferenced or pragma Unmodified. Also activates warnings for the case of Warnings (Off, String), where either there is no matching Warnings (On, String), or the Warnings (Off) did not suppress any warning. The default is that these warnings are not given.

-gnatw.W

‘Suppress warnings on unnecessary Warnings Off pragmas.’

This switch suppresses warnings for use of pragma Warnings (Off, ...).

-gnatwx

‘Activate warnings on Export/Import pragmas.’

This switch activates warnings on Export/Import pragmas when the compiler detects a possible conflict between the Ada and foreign language calling sequences. For example, the use of default parameters in a convention C procedure is dubious because the C compiler cannot supply the proper default, so a warning is issued. The default is that such warnings are generated.

-gnatwX

‘Suppress warnings on Export/Import pragmas.’

This switch suppresses warnings on Export/Import pragmas. The sense of this is that you are telling the compiler that you know what you are doing in writing the pragma, and it should not complain at you.

-gnatw.x

‘Activate warnings for No_Exception_Propagation mode.’

This switch activates warnings for exception usage when pragma Restrictions (No_Exception_Propagation) is in effect. Warnings are given for implicit or explicit exception raises which are not covered by a local handler, and for exception handlers which do not cover a local raise. The default is that these warnings are given for units that contain exception handlers.

-gnatw.X

‘Disable warnings for No_Exception_Propagation mode.’

This switch disables warnings for exception usage when pragma Restrictions (No_Exception_Propagation) is in effect.

-gnatwy

‘Activate warnings for Ada compatibility issues.’

For the most part, newer versions of Ada are upwards compatible with older versions. For example, Ada 2005 programs will almost always work when compiled as Ada 2012. However there are some exceptions (for example the fact that some is now a reserved word in Ada 2012). This switch activates several warnings to help in identifying and correcting such incompatibilities. The default is that these warnings are generated. Note that at one point Ada 2005 was called Ada 0Y, hence the choice of character.

-gnatwY

‘Disable warnings for Ada compatibility issues.’

This switch suppresses the warnings intended to help in identifying incompatibilities between Ada language versions.

-gnatw.y

‘Activate information messages for why package spec needs body.’

There are a number of cases in which a package spec needs a body. For example, the use of pragma Elaborate_Body, or the declaration of a procedure specification requiring a completion. This switch causes information messages to be output showing why a package specification requires a body. This can be useful in the case of a large package specification which is unexpectedly requiring a body. The default is that such information messages are not output.

-gnatw.Y

‘Disable information messages for why package spec needs body.’

This switch suppresses the output of information messages showing why a package specification needs a body.

-gnatwz

‘Activate warnings on unchecked conversions.’

This switch activates warnings for unchecked conversions where the types are known at compile time to have different sizes. The default is that such warnings are generated. Warnings are also generated for subprogram pointers with different conventions.

-gnatwZ

‘Suppress warnings on unchecked conversions.’

This switch suppresses warnings for unchecked conversions where the types are known at compile time to have different sizes or conventions.

-gnatw.z

‘Activate warnings for size not a multiple of alignment.’

This switch activates warnings for cases of array and record types with specified Size and Alignment attributes where the size is not a multiple of the alignment, resulting in an object size that is greater than the specified size. The default is that such warnings are generated.

-gnatw.Z

‘Suppress warnings for size not a multiple of alignment.’

This switch suppresses warnings for cases of array and record types with specified Size and Alignment attributes where the size is not a multiple of the alignment, resulting in an object size that is greater than the specified size. The warning can also be suppressed by giving an explicit Object_Size value.

-Wunused

The warnings controlled by the -gnatw switch are generated by the front end of the compiler. The GCC back end can provide additional warnings and they are controlled by the -W switch. For example, -Wunused activates back end warnings for entities that are declared but not referenced.

-Wuninitialized

Similarly, -Wuninitialized activates the back end warning for uninitialized variables. This switch must be used in conjunction with an optimization level greater than zero.

-Wstack-usage=`len'

Warn if the stack usage of a subprogram might be larger than len bytes. See Static Stack Usage Analysis for details.

-Wall

This switch enables most warnings from the GCC back end. The code generator detects a number of warning situations that are missed by the GNAT front end, and this switch can be used to activate them. The use of this switch also sets the default front-end warning mode to -gnatwa, that is, most front-end warnings are activated as well.

-w

Conversely, this switch suppresses warnings from the GCC back end. The use of this switch also sets the default front-end warning mode to -gnatws, that is, front-end warnings are suppressed as well.

-Werror

This switch causes warnings from the GCC back end to be treated as errors. The warning string still appears, but the warning messages are counted as errors, and prevent the generation of an object file. The use of this switch also sets the default front-end warning mode to -gnatwe, that is, front-end warning messages and style check messages are treated as errors as well.

A string of warning parameters can be used in the same parameter. For example:

-gnatwaGe

will turn on all optional warnings except for unrecognized pragma warnings, and also specify that warnings should be treated as errors.

When no switch -gnatw is used, this is equivalent to: