diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog index 61cb60a3a509608347ec90d5e852b7cfbbae56d2..f9e1bda9c2115346c158589df46cd1cbcb7fcdd4 100644 --- a/gcc/ada/ChangeLog +++ b/gcc/ada/ChangeLog @@ -1,3 +1,29 @@ +2011-08-02 Ed Falis <falis@adacore.com> + + * s-taprop-vxworks.adb, s-intman-vxworks.adb, s-intman-vxworks.ads: + Update header. + +2011-08-02 Bob Duff <duff@adacore.com> + + * opt.ads: Minor comment fix. + +2011-08-02 Bob Duff <duff@adacore.com> + + * sem_ch12.adb (Analyze_Package_Instantiation, + Analyze_Subprogram_Instantiation): Turn off style checking while + analyzing an instance. Whatever style checks that apply to the generic + unit should apply, so it makes no sense to apply them in an instance. + This was causing trouble when compiling an instance of a runtime + unit that violates the -gnatyO switch. + * stylesw.adb (Set_Style_Check_Options): "when 'O' =>" was missing from + one of the two case statements, causing spurious errors. + +2011-08-02 Robert Dewar <dewar@adacore.com> + + * uname.adb: Minor reformatting. + * gnatcmd.adb: Minor reformatting. + * exp_attr.adb: Minor reformatting. + 2011-08-02 Ed Schonberg <schonberg@adacore.com> * exp_ch5.adb (Expand_N_Assignment_Statement): under restriction diff --git a/gcc/ada/exp_attr.adb b/gcc/ada/exp_attr.adb index 008c8138dcb3fbc4e6d4f6dfd127ab9494d0e85c..8990e0b293b5660296f3a9caebaad959d1c494b2 100644 --- a/gcc/ada/exp_attr.adb +++ b/gcc/ada/exp_attr.adb @@ -5355,7 +5355,6 @@ package body Exp_Attr is Attribute_Universal_Literal_String | Attribute_Wchar_T_Size | Attribute_Word_Size => - raise Program_Error; -- The Asm_Input and Asm_Output attributes are not expanded at this @@ -5364,9 +5363,7 @@ package body Exp_Attr is when Attribute_Asm_Input | Attribute_Asm_Output => - null; - end case; exception @@ -5523,6 +5520,14 @@ package body Exp_Attr is -- in the run time used. In the case of a configurable run time, it -- is normal that some subprograms are not there. + -- I don't understand this routine at all, why is this not just a + -- call to RTE_Available? And if for some reason we need a different + -- routine with different semantics, why is not in Rtsfind ??? + + ------------------ + -- Is_Available -- + ------------------ + function Is_Available (Entity : RE_Id) return Boolean is begin -- Assume that the unit will always be available when using a @@ -5532,6 +5537,8 @@ package body Exp_Attr is or else RTE_Available (Entity); end Is_Available; + -- Start of processing for Find_Stream_Subprogram + begin if Present (Ent) then return Ent; @@ -5550,11 +5557,12 @@ package body Exp_Attr is -- This is disabled for AAMP, to avoid creating dependences on files not -- supported in the AAMP library (such as s-fileio.adb). - -- In the case of using a configurable run time, it is very likely + -- Note: In the case of using a configurable run time, it is very likely -- that stream routines for string types are not present (they require -- file system support). In this case, the specific stream routines for -- strings are not used, relying on the regular stream mechanism - -- instead. + -- instead. That is why we include the test Is_Available when dealing + -- with these cases. if VM_Target /= JVM_Target and then not AAMP_On_Target diff --git a/gcc/ada/gnatcmd.adb b/gcc/ada/gnatcmd.adb index cdd159a248a675f54b57f9988a387da9464665f2..8f22273725c75f947f1a71de8c696e2c141726ae 100644 --- a/gcc/ada/gnatcmd.adb +++ b/gcc/ada/gnatcmd.adb @@ -1356,9 +1356,7 @@ procedure GNATCmd is New_Line; end Non_VMS_Usage; - ------------------------------------- - -- Start of processing for GNATCmd -- - ------------------------------------- +-- Start of processing for GNATCmd begin -- Initializations diff --git a/gcc/ada/opt.ads b/gcc/ada/opt.ads index 61fc1f1e3f3b6047e3f02f6469259f3444f360a2..3f3b87256996e36dafed0d8573882286b902b78d 100644 --- a/gcc/ada/opt.ads +++ b/gcc/ada/opt.ads @@ -1184,7 +1184,7 @@ package Opt is Style_Check : Boolean := False; -- GNAT -- Set True to perform style checks. Activates checks carried out in - -- package Style (see body of this package for details of checks) This + -- package Style (see body of this package for details of checks). This -- flag is set True by either the -gnatg or -gnaty switches. Suppress_All_Inlining : Boolean := False; diff --git a/gcc/ada/s-intman-vxworks.adb b/gcc/ada/s-intman-vxworks.adb index 35ab83cee478ea46df77df061043dd44c9e5f604..f1576e9264428861546c3ec17cad34d74729b0d6 100644 --- a/gcc/ada/s-intman-vxworks.adb +++ b/gcc/ada/s-intman-vxworks.adb @@ -19,10 +19,10 @@ -- additional permissions described in the GCC Runtime Library Exception, -- -- version 3.1, as published by the Free Software Foundation. -- -- -- --- In particular, you can freely distribute your programs built with the -- --- GNAT Pro compiler, including any required library run-time units, using -- --- any licensing terms of your choosing. See the AdaCore Software License -- --- for full details. -- +-- You should have received a copy of the GNU General Public License and -- +-- a copy of the GCC Runtime Library Exception along with this program; -- +-- see the files COPYING3 and COPYING.RUNTIME respectively. If not, see -- +-- <http://www.gnu.org/licenses/>. -- -- -- -- GNARL was developed by the GNARL team at Florida State University. -- -- Extensive contributions were provided by Ada Core Technologies, Inc. -- diff --git a/gcc/ada/s-intman-vxworks.ads b/gcc/ada/s-intman-vxworks.ads index d73324d9bc712f594ca451646adf1d8ab2b29876..564c1391feac5ad49bc204fc44d81bd0c323de21 100644 --- a/gcc/ada/s-intman-vxworks.ads +++ b/gcc/ada/s-intman-vxworks.ads @@ -19,10 +19,10 @@ -- additional permissions described in the GCC Runtime Library Exception, -- -- version 3.1, as published by the Free Software Foundation. -- -- -- --- In particular, you can freely distribute your programs built with the -- --- GNAT Pro compiler, including any required library run-time units, using -- --- any licensing terms of your choosing. See the AdaCore Software License -- --- for full details. -- +-- You should have received a copy of the GNU General Public License and -- +-- a copy of the GCC Runtime Library Exception along with this program; -- +-- see the files COPYING3 and COPYING.RUNTIME respectively. If not, see -- +-- <http://www.gnu.org/licenses/>. -- -- -- -- GNARL was developed by the GNARL team at Florida State University. -- -- Extensive contributions were provided by Ada Core Technologies, Inc. -- diff --git a/gcc/ada/s-taprop-vxworks.adb b/gcc/ada/s-taprop-vxworks.adb index c2b04a55c573f3ea3deb75f8628df76c50ee211c..d51a2ebaa7b477cc248db29095d78157bd69efa0 100644 --- a/gcc/ada/s-taprop-vxworks.adb +++ b/gcc/ada/s-taprop-vxworks.adb @@ -19,10 +19,10 @@ -- additional permissions described in the GCC Runtime Library Exception, -- -- version 3.1, as published by the Free Software Foundation. -- -- -- --- In particular, you can freely distribute your programs built with the -- --- GNAT Pro compiler, including any required library run-time units, using -- --- any licensing terms of your choosing. See the AdaCore Software License -- --- for full details. -- +-- You should have received a copy of the GNU General Public License and -- +-- a copy of the GCC Runtime Library Exception along with this program; -- +-- see the files COPYING3 and COPYING.RUNTIME respectively. If not, see -- +-- <http://www.gnu.org/licenses/>. -- -- -- -- GNARL was developed by the GNARL team at Florida State University. -- -- Extensive contributions were provided by Ada Core Technologies, Inc. -- diff --git a/gcc/ada/sem_ch12.adb b/gcc/ada/sem_ch12.adb index 81c59d5e124fab386faf2e87ec2737cf3e2100c5..218028f7ddfdb486f197aba41e4839dd6cf60b7a 100644 --- a/gcc/ada/sem_ch12.adb +++ b/gcc/ada/sem_ch12.adb @@ -2975,6 +2975,8 @@ package body Sem_Ch12 is return False; end Might_Inline_Subp; + Save_Style_Check : constant Boolean := Style_Check; + -- Start of processing for Analyze_Package_Instantiation begin @@ -2987,6 +2989,12 @@ package body Sem_Ch12 is Instantiation_Node := N; + -- Turn off style checking in instances. If the check is enabled on the + -- generic unit, a warning in an instance would just be noise. If not + -- enabled on the generic, then a warning in an instance is just wrong. + + Style_Check := False; + -- Case of instantiation of a generic package if Nkind (N) = N_Package_Instantiation then @@ -3571,6 +3579,8 @@ package body Sem_Ch12 is Set_Defining_Identifier (N, Act_Decl_Id); end if; + Style_Check := Save_Style_Check; + <<Leave>> if Has_Aspects (N) then Analyze_Aspect_Specifications (N, Act_Decl_Id); @@ -3585,6 +3595,8 @@ package body Sem_Ch12 is if Env_Installed then Restore_Env; end if; + + Style_Check := Save_Style_Check; end Analyze_Package_Instantiation; -------------------------- @@ -4104,6 +4116,8 @@ package body Sem_Ch12 is end if; end Analyze_Instance_And_Renamings; + Save_Style_Check : constant Boolean := Style_Check; + -- Start of processing for Analyze_Subprogram_Instantiation begin @@ -4117,6 +4131,13 @@ package body Sem_Ch12 is -- Make node global for error reporting Instantiation_Node := N; + + -- Turn off style checking in instances. If the check is enabled on the + -- generic unit, a warning in an instance would just be noise. If not + -- enabled on the generic, then a warning in an instance is just wrong. + + Style_Check := False; + Preanalyze_Actuals (N); Init_Env; @@ -4352,6 +4373,8 @@ package body Sem_Ch12 is Generic_Renamings_HTable.Reset; end if; + Style_Check := Save_Style_Check; + <<Leave>> if Has_Aspects (N) then Analyze_Aspect_Specifications (N, Act_Decl_Id); @@ -4366,6 +4389,8 @@ package body Sem_Ch12 is if Env_Installed then Restore_Env; end if; + + Style_Check := Save_Style_Check; end Analyze_Subprogram_Instantiation; ------------------------- diff --git a/gcc/ada/stylesw.adb b/gcc/ada/stylesw.adb index 9a59996558713e5150a4a5de847e7f7d7f71dbdd..7c9d462cc234e10b1b3c40f07a961bd79f0f85ac 100644 --- a/gcc/ada/stylesw.adb +++ b/gcc/ada/stylesw.adb @@ -530,6 +530,9 @@ package body Stylesw is when 'o' => Style_Check_Order_Subprograms := False; + when 'O' => + Style_Check_Missing_Overriding := False; + when 'p' => Style_Check_Pragma_Casing := False; diff --git a/gcc/ada/uname.adb b/gcc/ada/uname.adb index 9628867ae0ca58f60132b39601f268880ae8389c..eb514b75c2383be31dd599c3192c7ef338fd5a12 100644 --- a/gcc/ada/uname.adb +++ b/gcc/ada/uname.adb @@ -349,9 +349,7 @@ package body Uname is return N; end Get_Parent; - ------------------------------------------- - -- Start of Processing for Get_Unit_Name -- - ------------------------------------------- + -- Start of processing for Get_Unit_Name begin Node := N;