Commit 8c64de1e by Robert Dewar Committed by Arnaud Charlet

s-conca5.adb, [...]: Remove unneeded pragma Warnings

2009-04-17  Robert Dewar  <dewar@adacore.com>

	* s-conca5.adb, g-sercom.adb, s-conca5.ads, s-conca7.adb, exp_imgv.adb,
	s-conca7.ads, s-crc32.adb, s-crc32.ads, s-conca9.adb, s-conca9.ads,
	s-addope.adb, i-cstrin.ads, s-addope.ads, s-carun8.adb, s-carun8.ads,
	g-htable.ads, g-hesora.adb, g-hesora.ads, s-htable.adb, s-htable.ads,
	s-conca2.adb, s-conca2.ads, a-except.adb, s-conca4.adb, a-except.ads,
	s-conca4.ads, s-except.adb, s-except.ads, s-conca6.adb, s-conca6.ads,
	g-spchge.adb, g-spchge.ads, g-u3spch.adb, g-u3spch.ads, s-conca8.adb,
	s-conca8.ads, g-byorma.adb, g-byorma.ads, s-memory.adb, s-memory.ads,
	g-speche.adb, g-speche.ads, g-stsifd-sockets.adb, exp_dist.adb,
	s-imgenu.adb, s-imgenu.ads, s-mastop.adb, s-mastop.ads, s-exctab.adb,
	s-exctab.ads, s-imenne.adb, s-imenne.ads, s-casuti.adb, osint.adb,
	s-assert.adb, s-casuti.ads, s-assert.ads, s-os_lib.adb, s-conca3.adb,
	s-conca3.ads: Remove unneeded pragma Warnings

From-SVN: r146263
parent 74e63df1
2009-04-17 Robert Dewar <dewar@adacore.com> 2009-04-17 Robert Dewar <dewar@adacore.com>
* s-conca5.adb, g-sercom.adb, s-conca5.ads, s-conca7.adb, exp_imgv.adb,
s-conca7.ads, s-crc32.adb, s-crc32.ads, s-conca9.adb, s-conca9.ads,
s-addope.adb, i-cstrin.ads, s-addope.ads, s-carun8.adb, s-carun8.ads,
g-htable.ads, g-hesora.adb, g-hesora.ads, s-htable.adb, s-htable.ads,
s-conca2.adb, s-conca2.ads, a-except.adb, s-conca4.adb, a-except.ads,
s-conca4.ads, s-except.adb, s-except.ads, s-conca6.adb, s-conca6.ads,
g-spchge.adb, g-spchge.ads, g-u3spch.adb, g-u3spch.ads, s-conca8.adb,
s-conca8.ads, g-byorma.adb, g-byorma.ads, s-memory.adb, s-memory.ads,
g-speche.adb, g-speche.ads, g-stsifd-sockets.adb, exp_dist.adb,
s-imgenu.adb, s-imgenu.ads, s-mastop.adb, s-mastop.ads, s-exctab.adb,
s-exctab.ads, s-imenne.adb, s-imenne.ads, s-casuti.adb, osint.adb,
s-assert.adb, s-casuti.ads, s-assert.ads, s-os_lib.adb, s-conca3.adb,
s-conca3.ads: Remove unneeded pragma Warnings
2009-04-17 Robert Dewar <dewar@adacore.com>
* g-moreex.adb: Add comments. * g-moreex.adb: Add comments.
* s-auxdec.ads: Add ??? comment for uncommented pragma Warnings (Off) * s-auxdec.ads: Add ??? comment for uncommented pragma Warnings (Off)
...@@ -40,9 +40,7 @@ ...@@ -40,9 +40,7 @@
-- 2005 functionality is required. In particular, it is used for building -- 2005 functionality is required. In particular, it is used for building
-- run times on all targets. -- run times on all targets.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
pragma Style_Checks (All_Checks); pragma Style_Checks (All_Checks);
-- No subprogram ordering check, due to logical grouping -- No subprogram ordering check, due to logical grouping
......
...@@ -44,14 +44,12 @@ ...@@ -44,14 +44,12 @@
-- 2005 functionality is required. In particular, it is used for building -- 2005 functionality is required. In particular, it is used for building
-- run times on all targets. -- run times on all targets.
pragma Compiler_Unit;
pragma Polling (Off); pragma Polling (Off);
-- We must turn polling off for this unit, because otherwise we get -- We must turn polling off for this unit, because otherwise we get
-- elaboration circularities with ourself. -- elaboration circularities with ourself.
pragma Warnings (Off);
pragma Compiler_Unit;
pragma Warnings (On);
with System; with System;
with System.Parameters; with System.Parameters;
with System.Standard_Library; with System.Standard_Library;
......
...@@ -3645,9 +3645,7 @@ package body Exp_Dist is ...@@ -3645,9 +3645,7 @@ package body Exp_Dist is
(Vis_Decl : Node_Id; (Vis_Decl : Node_Id;
RAS_Type : Entity_Id) RAS_Type : Entity_Id)
is is
pragma Warnings (Off);
pragma Unreferenced (RAS_Type); pragma Unreferenced (RAS_Type);
pragma Warnings (On);
begin begin
Add_RAS_Access_TSS (Vis_Decl); Add_RAS_Access_TSS (Vis_Decl);
end Add_RAST_Features; end Add_RAST_Features;
...@@ -4111,10 +4109,8 @@ package body Exp_Dist is ...@@ -4111,10 +4109,8 @@ package body Exp_Dist is
-- List of statements for extra formal parameters. It will appear -- List of statements for extra formal parameters. It will appear
-- after the regular statements for writing out parameters. -- after the regular statements for writing out parameters.
pragma Warnings (Off);
pragma Unreferenced (RACW_Type); pragma Unreferenced (RACW_Type);
-- Used only for the PolyORB case -- Used only for the PolyORB case
pragma Warnings (On);
begin begin
-- The general form of a calling stub for a given subprogram is: -- The general form of a calling stub for a given subprogram is:
...@@ -5601,9 +5597,7 @@ package body Exp_Dist is ...@@ -5601,9 +5597,7 @@ package body Exp_Dist is
RPC_Receiver_Decl : Node_Id; RPC_Receiver_Decl : Node_Id;
Body_Decls : List_Id) Body_Decls : List_Id)
is is
pragma Warnings (Off);
pragma Unreferenced (RPC_Receiver_Decl); pragma Unreferenced (RPC_Receiver_Decl);
pragma Warnings (On);
begin begin
Add_RACW_From_Any Add_RACW_From_Any
...@@ -5730,9 +5724,8 @@ package body Exp_Dist is ...@@ -5730,9 +5724,8 @@ package body Exp_Dist is
Stub_Type_Access : Entity_Id; Stub_Type_Access : Entity_Id;
Body_Decls : List_Id) Body_Decls : List_Id)
is is
pragma Warnings (Off);
pragma Unreferenced (Stub_Type, Stub_Type_Access); pragma Unreferenced (Stub_Type, Stub_Type_Access);
pragma Warnings (On);
Loc : constant Source_Ptr := Sloc (RACW_Type); Loc : constant Source_Ptr := Sloc (RACW_Type);
Proc_Decl : Node_Id; Proc_Decl : Node_Id;
...@@ -6047,9 +6040,7 @@ package body Exp_Dist is ...@@ -6047,9 +6040,7 @@ package body Exp_Dist is
Stub_Type_Access : Entity_Id; Stub_Type_Access : Entity_Id;
Body_Decls : List_Id) Body_Decls : List_Id)
is is
pragma Warnings (Off);
pragma Unreferenced (Stub_Type, Stub_Type_Access); pragma Unreferenced (Stub_Type, Stub_Type_Access);
pragma Warnings (On);
Loc : constant Source_Ptr := Sloc (RACW_Type); Loc : constant Source_Ptr := Sloc (RACW_Type);
...@@ -7629,9 +7620,8 @@ package body Exp_Dist is ...@@ -7629,9 +7620,8 @@ package body Exp_Dist is
RPC_Receiver_Decl : out Node_Id) RPC_Receiver_Decl : out Node_Id)
is is
Loc : constant Source_Ptr := Sloc (Stub_Type); Loc : constant Source_Ptr := Sloc (Stub_Type);
pragma Warnings (Off);
pragma Unreferenced (RACW_Type); pragma Unreferenced (RACW_Type);
pragma Warnings (On);
begin begin
Stub_Type_Decl := Stub_Type_Decl :=
...@@ -9894,9 +9884,7 @@ package body Exp_Dist is ...@@ -9894,9 +9884,7 @@ package body Exp_Dist is
Counter : Entity_Id; Counter : Entity_Id;
Datum : Node_Id) Datum : Node_Id)
is is
pragma Warnings (Off);
pragma Unreferenced (Counter); pragma Unreferenced (Counter);
pragma Warnings (On);
Element_Any : Node_Id; Element_Any : Node_Id;
...@@ -10387,9 +10375,7 @@ package body Exp_Dist is ...@@ -10387,9 +10375,7 @@ package body Exp_Dist is
Rec : Entity_Id; Rec : Entity_Id;
Field : Node_Id) Field : Node_Id)
is is
pragma Warnings (Off);
pragma Unreferenced (Any, Counter, Rec); pragma Unreferenced (Any, Counter, Rec);
pragma Warnings (On);
begin begin
if Nkind (Field) = N_Defining_Identifier then if Nkind (Field) = N_Defining_Identifier then
......
...@@ -1158,9 +1158,8 @@ package body Exp_Imgv is ...@@ -1158,9 +1158,8 @@ package body Exp_Imgv is
-- as is done with other ZFP violations. -- as is done with other ZFP violations.
declare declare
pragma Warnings (Off); -- since Discard is unreferenced
Discard : constant Entity_Id := RTE (RE_Null); Discard : constant Entity_Id := RTE (RE_Null);
pragma Warnings (On); pragma Unreferenced (Discard);
begin begin
return; return;
end; end;
......
...@@ -31,6 +31,8 @@ ...@@ -31,6 +31,8 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Compiler_Unit;
package body GNAT.Byte_Order_Mark is package body GNAT.Byte_Order_Mark is
-------------- --------------
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 2006-2007, AdaCore -- -- Copyright (C) 2006-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -63,9 +63,7 @@ ...@@ -63,9 +63,7 @@
-- cases depend on the first character of the XML file being < so that the -- cases depend on the first character of the XML file being < so that the
-- encoding of this character can be recognized. -- encoding of this character can be recognized.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package GNAT.Byte_Order_Mark is package GNAT.Byte_Order_Mark is
......
...@@ -31,9 +31,7 @@ ...@@ -31,9 +31,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body GNAT.Heap_Sort_A is package body GNAT.Heap_Sort_A is
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 1995-2007, AdaCore -- -- Copyright (C) 1995-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -42,9 +42,7 @@ ...@@ -42,9 +42,7 @@
-- worst case and is in place with no additional storage required. See -- worst case and is in place with no additional storage required. See
-- the body for exact details of the algorithm used. -- the body for exact details of the algorithm used.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package GNAT.Heap_Sort_A is package GNAT.Heap_Sort_A is
pragma Preelaborate; pragma Preelaborate;
......
...@@ -43,9 +43,7 @@ ...@@ -43,9 +43,7 @@
-- this facility is accessed from run time routines, but clients should -- this facility is accessed from run time routines, but clients should
-- always access the version supplied via GNAT.HTable. -- always access the version supplied via GNAT.HTable.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with System.HTable; with System.HTable;
......
...@@ -67,7 +67,8 @@ package body GNAT.Serial_Communications is ...@@ -67,7 +67,8 @@ package body GNAT.Serial_Communications is
procedure Open procedure Open
(Port : out Serial_Port; (Port : out Serial_Port;
Name : Port_Name) is Name : Port_Name)
is
begin begin
Unimplemented; Unimplemented;
end Open; end Open;
...@@ -83,7 +84,8 @@ package body GNAT.Serial_Communications is ...@@ -83,7 +84,8 @@ package body GNAT.Serial_Communications is
Stop_Bits : Stop_Bits_Number := One; Stop_Bits : Stop_Bits_Number := One;
Parity : Parity_Check := None; Parity : Parity_Check := None;
Block : Boolean := True; Block : Boolean := True;
Timeout : Duration := 10.0) is Timeout : Duration := 10.0)
is
begin begin
Unimplemented; Unimplemented;
end Set; end Set;
...@@ -95,7 +97,8 @@ package body GNAT.Serial_Communications is ...@@ -95,7 +97,8 @@ package body GNAT.Serial_Communications is
overriding procedure Read overriding procedure Read
(Port : in out Serial_Port; (Port : in out Serial_Port;
Buffer : out Stream_Element_Array; Buffer : out Stream_Element_Array;
Last : out Stream_Element_Offset) is Last : out Stream_Element_Offset)
is
begin begin
Unimplemented; Unimplemented;
end Read; end Read;
...@@ -106,7 +109,8 @@ package body GNAT.Serial_Communications is ...@@ -106,7 +109,8 @@ package body GNAT.Serial_Communications is
overriding procedure Write overriding procedure Write
(Port : in out Serial_Port; (Port : in out Serial_Port;
Buffer : Stream_Element_Array) is Buffer : Stream_Element_Array)
is
begin begin
Unimplemented; Unimplemented;
end Write; end Write;
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- B o d y -- -- B o d y --
-- -- -- --
-- Copyright (C) 1998-2007, AdaCore -- -- Copyright (C) 1998-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -31,9 +31,7 @@ ...@@ -31,9 +31,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body GNAT.Spelling_Checker_Generic is package body GNAT.Spelling_Checker_Generic is
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 1998-2007, AdaCore -- -- Copyright (C) 1998-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -39,9 +39,7 @@ ...@@ -39,9 +39,7 @@
-- codes for ASCII characters in the range 16#20#..16#7F# have their normal -- codes for ASCII characters in the range 16#20#..16#7F# have their normal
-- expected encoding values (e.g. the Pos value 16#31# must be digit 1). -- expected encoding values (e.g. the Pos value 16#31# must be digit 1).
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package GNAT.Spelling_Checker_Generic is package GNAT.Spelling_Checker_Generic is
pragma Pure; pragma Pure;
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- B o d y -- -- B o d y --
-- -- -- --
-- Copyright (C) 1998-2007, AdaCore -- -- Copyright (C) 1998-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -31,9 +31,7 @@ ...@@ -31,9 +31,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with GNAT.Spelling_Checker_Generic; with GNAT.Spelling_Checker_Generic;
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 1998-2007, AdaCore -- -- Copyright (C) 1998-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -36,9 +36,7 @@ ...@@ -36,9 +36,7 @@
-- This package provides a utility routine for checking for bad spellings -- This package provides a utility routine for checking for bad spellings
-- for the case of String arguments. -- for the case of String arguments.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package GNAT.Spelling_Checker is package GNAT.Spelling_Checker is
pragma Pure; pragma Pure;
......
...@@ -67,7 +67,8 @@ package body Signalling_Fds is ...@@ -67,7 +67,8 @@ package body Signalling_Fds is
-- Address of listening socket -- Address of listening socket
Res : C.int; Res : C.int;
-- Return status of system calls pragma Warnings (Off, Res);
-- Return status of system calls (usually ignored, hence warnings off)
begin begin
Fds.all := (Read_End | Write_End => Failure); Fds.all := (Read_End | Write_End => Failure);
...@@ -153,9 +154,7 @@ package body Signalling_Fds is ...@@ -153,9 +154,7 @@ package body Signalling_Fds is
pragma Assert (Res = Failure pragma Assert (Res = Failure
and then and then
Socket_Errno = SOSC.EADDRINUSE); Socket_Errno = SOSC.EADDRINUSE);
pragma Warnings (Off); -- useless assignment to "Res"
Res := C_Close (W_Sock); Res := C_Close (W_Sock);
pragma Warnings (On);
W_Sock := Failure; W_Sock := Failure;
Res := C_Close (R_Sock); Res := C_Close (R_Sock);
R_Sock := Failure; R_Sock := Failure;
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- B o d y -- -- B o d y --
-- -- -- --
-- Copyright (C) 1998-2007, AdaCore -- -- Copyright (C) 1998-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -31,9 +31,7 @@ ...@@ -31,9 +31,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with GNAT.Spelling_Checker_Generic; with GNAT.Spelling_Checker_Generic;
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- S p e c -- -- S p e c --
-- -- -- --
-- Copyright (C) 1998-2007, AdaCore -- -- Copyright (C) 1998-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -36,9 +36,7 @@ ...@@ -36,9 +36,7 @@
-- This package provides a utility routine for checking for bad spellings -- This package provides a utility routine for checking for bad spellings
-- for the case of System.WCh_Cnv.UTF_32_String arguments. -- for the case of System.WCh_Cnv.UTF_32_String arguments.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with System.WCh_Cnv; with System.WCh_Cnv;
......
...@@ -38,14 +38,10 @@ package Interfaces.C.Strings is ...@@ -38,14 +38,10 @@ package Interfaces.C.Strings is
type char_array_access is access all char_array; type char_array_access is access all char_array;
pragma Warnings (Off);
pragma No_Strict_Aliasing (char_array_access); pragma No_Strict_Aliasing (char_array_access);
pragma Warnings (On);
-- Since this type is used for external interfacing, with the pointer -- Since this type is used for external interfacing, with the pointer
-- coming from who knows where, it seems a good idea to turn off any -- coming from who knows where, it seems a good idea to turn off any
-- strict aliasing assumptions for this type. We turn off warnings for -- strict aliasing assumptions for this type.
-- this pragma to deal with being compiled with an earlier GNAT version
-- that does not recognize this pragma.
type chars_ptr is private; type chars_ptr is private;
......
...@@ -300,7 +300,7 @@ package body Osint is ...@@ -300,7 +300,7 @@ package body Osint is
Status : Boolean; Status : Boolean;
pragma Warnings (Off, Status); pragma Warnings (Off, Status);
-- For the call to Close -- For the call to Close where status is ignored
begin begin
File_FD := Open_Read (Buffer'Address, Binary); File_FD := Open_Read (Buffer'Address, Binary);
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with Ada.Unchecked_Conversion; with Ada.Unchecked_Conversion;
......
...@@ -40,9 +40,7 @@ ...@@ -40,9 +40,7 @@
-- inappropriate use by applications programs). In addition, the logical -- inappropriate use by applications programs). In addition, the logical
-- operations may not be available if type Address is a signed integer. -- operations may not be available if type Address is a signed integer.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Address_Operations is package System.Address_Operations is
pragma Pure; pragma Pure;
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with Ada.Exceptions; with Ada.Exceptions;
with System.Exceptions; with System.Exceptions;
......
...@@ -34,9 +34,7 @@ ...@@ -34,9 +34,7 @@
-- This unit may be used directly from an application program by providing -- This unit may be used directly from an application program by providing
-- an appropriate WITH, and the interface can be expected to remain stable. -- an appropriate WITH, and the interface can be expected to remain stable.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Assertions is package System.Assertions is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with System.Address_Operations; use System.Address_Operations; with System.Address_Operations; use System.Address_Operations;
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains functions for runtime comparisons on arrays whose -- This package contains functions for runtime comparisons on arrays whose
-- elements are 8-bit discrete type values to be treated as unsigned. -- elements are 8-bit discrete type values to be treated as unsigned.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Compare_Array_Unsigned_8 is package System.Compare_Array_Unsigned_8 is
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- B o d y -- -- B o d y --
-- -- -- --
-- Copyright (C) 1995-2007, AdaCore -- -- Copyright (C) 1995-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -31,9 +31,7 @@ ...@@ -31,9 +31,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Case_Util is package body System.Case_Util is
......
...@@ -37,9 +37,7 @@ ...@@ -37,9 +37,7 @@
-- Note that all the routines in this package are available to the user -- Note that all the routines in this package are available to the user
-- via GNAT.Case_Util, which imports all the entities from this package. -- via GNAT.Case_Util, which imports all the entities from this package.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Case_Util is package System.Case_Util is
pragma Pure; pragma Pure;
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_2 is package body System.Concat_2 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of two string -- This package contains a procedure for runtime concatenation of two string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_2 is package System.Concat_2 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_3 is package body System.Concat_3 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of three string -- This package contains a procedure for runtime concatenation of three string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_3 is package System.Concat_3 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_4 is package body System.Concat_4 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of four string -- This package contains a procedure for runtime concatenation of four string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_4 is package System.Concat_4 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_5 is package body System.Concat_5 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of five string -- This package contains a procedure for runtime concatenation of five string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_5 is package System.Concat_5 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_6 is package body System.Concat_6 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of six string -- This package contains a procedure for runtime concatenation of six string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_6 is package System.Concat_6 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_7 is package body System.Concat_7 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of seven string -- This package contains a procedure for runtime concatenation of seven string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_7 is package System.Concat_7 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_8 is package body System.Concat_8 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of eight string -- This package contains a procedure for runtime concatenation of eight string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_8 is package System.Concat_8 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Concat_9 is package body System.Concat_9 is
......
...@@ -32,9 +32,7 @@ ...@@ -32,9 +32,7 @@
-- This package contains a procedure for runtime concatenation of eight string -- This package contains a procedure for runtime concatenation of eight string
-- operands. It is used when we want to save space in the generated code. -- operands. It is used when we want to save space in the generated code.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Concat_9 is package System.Concat_9 is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.CRC32 is package body System.CRC32 is
......
...@@ -54,9 +54,7 @@ ...@@ -54,9 +54,7 @@
-- "Computation of Cyclic Redundancy Checks via Table Look-Up", Communications -- "Computation of Cyclic Redundancy Checks via Table Look-Up", Communications
-- of the ACM, Vol. 31 No. 8, pp.1008-1013 Aug. 1988. Sarwate, D.V. -- of the ACM, Vol. 31 No. 8, pp.1008-1013 Aug. 1988. Sarwate, D.V.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with Interfaces; with Interfaces;
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Exceptions is package body System.Exceptions is
......
...@@ -33,17 +33,13 @@ ...@@ -33,17 +33,13 @@
-- It should be compiled without optimization to let debuggers inspect -- It should be compiled without optimization to let debuggers inspect
-- parameter values reliably from breakpoints on the routines. -- parameter values reliably from breakpoints on the routines.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with System.Standard_Library; with System.Standard_Library;
package System.Exceptions is package System.Exceptions is
pragma Warnings (Off);
pragma Preelaborate_05; pragma Preelaborate_05;
pragma Warnings (On);
-- To let Ada.Exceptions "with" us and let us "with" Standard_Library -- To let Ada.Exceptions "with" us and let us "with" Standard_Library
package SSL renames System.Standard_Library; package SSL renames System.Standard_Library;
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with System.HTable; with System.HTable;
with System.Soft_Links; use System.Soft_Links; with System.Soft_Links; use System.Soft_Links;
......
...@@ -33,9 +33,7 @@ ...@@ -33,9 +33,7 @@
-- registered exception names, for the implementation of the mapping -- registered exception names, for the implementation of the mapping
-- of names to exceptions (used for exception streams and attributes) -- of names to exceptions (used for exception streams and attributes)
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with System.Standard_Library; with System.Standard_Library;
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- B o d y -- -- B o d y --
-- -- -- --
-- Copyright (C) 1995-2007, AdaCore -- -- Copyright (C) 1995-2008, AdaCore --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -31,9 +31,7 @@ ...@@ -31,9 +31,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with Ada.Unchecked_Deallocation; with Ada.Unchecked_Deallocation;
......
...@@ -39,9 +39,7 @@ ...@@ -39,9 +39,7 @@
-- The Static_HTable package provides a more complex interface that allows -- The Static_HTable package provides a more complex interface that allows
-- complete control over allocation. -- complete control over allocation.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.HTable is package System.HTable is
pragma Preelaborate; pragma Preelaborate;
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with Ada.Unchecked_Conversion; with Ada.Unchecked_Conversion;
......
...@@ -40,9 +40,7 @@ ...@@ -40,9 +40,7 @@
-- for bootstrapping with older versions of the compiler which expect to find -- for bootstrapping with older versions of the compiler which expect to find
-- functions in this package. -- functions in this package.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Img_Enum_New is package System.Img_Enum_New is
pragma Pure; pragma Pure;
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with Ada.Unchecked_Conversion; with Ada.Unchecked_Conversion;
......
...@@ -41,9 +41,7 @@ ...@@ -41,9 +41,7 @@
-- these functions. The new compiler will search for procedures in the new -- these functions. The new compiler will search for procedures in the new
-- version of the unit. -- version of the unit.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Img_Enum is package System.Img_Enum is
pragma Pure; pragma Pure;
......
...@@ -33,9 +33,7 @@ ...@@ -33,9 +33,7 @@
-- This dummy version of System.Machine_State_Operations is used -- This dummy version of System.Machine_State_Operations is used
-- on targets for which zero cost exception handling is not implemented. -- on targets for which zero cost exception handling is not implemented.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package body System.Machine_State_Operations is package body System.Machine_State_Operations is
......
...@@ -29,9 +29,7 @@ ...@@ -29,9 +29,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
pragma Polling (Off); pragma Polling (Off);
-- We must turn polling off for this unit, because otherwise we get -- We must turn polling off for this unit, because otherwise we get
......
...@@ -41,9 +41,7 @@ ...@@ -41,9 +41,7 @@
-- you can remove the calls to Abort_Defer.all and Abort_Undefer.all from -- you can remove the calls to Abort_Defer.all and Abort_Undefer.all from
-- this unit. -- this unit.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with Ada.Exceptions; with Ada.Exceptions;
with System.Soft_Links; with System.Soft_Links;
......
...@@ -40,9 +40,7 @@ ...@@ -40,9 +40,7 @@
-- This unit may be used directly from an application program by providing -- This unit may be used directly from an application program by providing
-- an appropriate WITH, and the interface can be expected to remain stable. -- an appropriate WITH, and the interface can be expected to remain stable.
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
package System.Memory is package System.Memory is
pragma Elaborate_Body; pragma Elaborate_Body;
......
...@@ -31,9 +31,7 @@ ...@@ -31,9 +31,7 @@
-- -- -- --
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
pragma Warnings (Off);
pragma Compiler_Unit; pragma Compiler_Unit;
pragma Warnings (On);
with System.Case_Util; with System.Case_Util;
with System.CRTL; with System.CRTL;
......
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