OSDN Git Service

2009-07-22 Thomas Quinot <quinot@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / gnat1drv.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             G N A T 1 D R V                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2009, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Atree;    use Atree;
27 with Back_End; use Back_End;
28 with Comperr;
29 with Csets;    use Csets;
30 with Debug;    use Debug;
31 with Elists;
32 with Errout;   use Errout;
33 with Fmap;
34 with Fname;    use Fname;
35 with Fname.UF; use Fname.UF;
36 with Frontend;
37 with Gnatvsn;  use Gnatvsn;
38 with Hostparm;
39 with Inline;
40 with Lib;      use Lib;
41 with Lib.Writ; use Lib.Writ;
42 with Lib.Xref;
43 with Namet;    use Namet;
44 with Nlists;
45 with Opt;      use Opt;
46 with Osint;    use Osint;
47 with Output;   use Output;
48 with Par_SCO;
49 with Prepcomp;
50 with Repinfo;  use Repinfo;
51 with Restrict;
52 with Rtsfind;
53 with Sem;
54 with Sem_Ch8;
55 with Sem_Ch12;
56 with Sem_Ch13;
57 with Sem_Elim;
58 with Sem_Eval;
59 with Sem_Type;
60 with Sinfo;    use Sinfo;
61 with Sinput.L; use Sinput.L;
62 with Snames;
63 with Sprint;   use Sprint;
64 with Stringt;
65 with Stylesw;  use Stylesw;
66 with Targparm; use Targparm;
67 with Tree_Gen;
68 with Treepr;   use Treepr;
69 with Ttypes;
70 with Types;    use Types;
71 with Uintp;    use Uintp;
72 with Uname;    use Uname;
73 with Urealp;
74 with Usage;
75 with Validsw;  use Validsw;
76
77 with System.Assertions;
78
79 procedure Gnat1drv is
80    Main_Unit_Node : Node_Id;
81    --  Compilation unit node for main unit
82
83    Main_Kind : Node_Kind;
84    --  Kind of main compilation unit node
85
86    Back_End_Mode : Back_End.Back_End_Mode_Type;
87    --  Record back end mode
88
89    procedure Adjust_Global_Switches;
90    --  There are various interactions between front end switch settings,
91    --  including debug switch settings and target dependent parameters.
92    --  This procedure takes care of properly handling these interactions.
93    --  We do it after scanning out all the switches, so that we are not
94    --  depending on the order in which switches appear.
95
96    procedure Check_Bad_Body;
97    --  Called to check if the unit we are compiling has a bad body
98
99    procedure Check_Rep_Info;
100    --  Called when we are not generating code, to check if -gnatR was requested
101    --  and if so, explain that we will not be honoring the request.
102
103    procedure Check_Library_Items;
104    --  For debugging -- checks the behavior of Walk_Library_Items
105    pragma Warnings (Off, Check_Library_Items);
106    --  In case the call below is commented out
107
108    ----------------------------
109    -- Adjust_Global_Switches --
110    ----------------------------
111
112    procedure Adjust_Global_Switches is
113    begin
114       --  Debug flag -gnatd.I is a synonym of Generate_SCIL
115
116       if Debug_Flag_Dot_II then
117          Generate_SCIL := True;
118       end if;
119
120       --  Set ASIS mode if -gnatt and -gnatc are set
121
122       if Operating_Mode = Check_Semantics and then Tree_Output then
123          ASIS_Mode := True;
124
125          --  Turn off inlining in ASIS mode, since ASIS cannot handle the extra
126          --  information in the trees caused by inlining being active.
127
128          --  More specifically, the tree seems to be malformed from the ASIS
129          --  point of view if -gnatc and -gnatn appear together???
130
131          Inline_Active := False;
132
133          --  Turn off SCIL generation in ASIS mode, since SCIL requires front-
134          --  end expansion.
135
136          Generate_SCIL := False;
137       end if;
138
139       --  SCIL mode needs to disable front-end inlining since the generated
140       --  trees (in particular order and consistency between specs compiled
141       --  as part of a main unit or as part of a with-clause) are causing
142       --  troubles.
143
144       if Generate_SCIL then
145          Front_End_Inlining := False;
146       end if;
147
148       --  Tune settings for optimal SCIL generation in CodePeer_Mode
149
150       if CodePeer_Mode then
151
152          --  Turn off inlining, confuses CodePeer output and gains nothing
153
154          Front_End_Inlining := False;
155          Inline_Active      := False;
156
157          --  Turn off ASIS mode: incompatible with front-end expansion.
158
159          ASIS_Mode := False;
160
161          --  Suppress overflow checks and access checks since they are handled
162          --  implicitly by CodePeer.
163
164          --  Turn off dynamic elaboration checks: generates inconsistencies in
165          --  trees between specs compiled as part of a main unit or as part of
166          --  a with-clause.
167
168          --  Enable all other language checks
169
170          Suppress_Options :=
171            (Overflow_Check    => True,
172             Access_Check      => True,
173             Elaboration_Check => True,
174             others            => False);
175          Enable_Overflow_Checks := False;
176          Dynamic_Elaboration_Checks := False;
177
178          --  Kill debug of generated code, since it messes up sloc values
179
180          Debug_Generated_Code := False;
181
182          --  Turn cross-referencing on in case it was disabled (by e.g. -gnatD)
183          --  Do we really need to spend time generating xref in CodePeer
184          --  mode??? Consider setting Xref_Active to False.
185
186          Xref_Active := True;
187
188          --  Polling mode forced off, since it generates confusing junk
189
190          Polling_Required := False;
191
192          --  Set operating mode to Generate_Code to benefit from full
193          --  front-end expansion (e.g. generics).
194
195          Operating_Mode := Generate_Code;
196
197          --  We need SCIL generation of course
198
199          Generate_SCIL := True;
200
201          --  Enable assertions and debug pragmas, since they give CodePeer
202          --  valuable extra information.
203
204          Assertions_Enabled     := True;
205          Debug_Pragmas_Enabled  := True;
206
207          --  Suppress compiler warnings, since what we are interested in here
208          --  is what CodePeer can find out. Also disable all simple value
209          --  propagation. This is an optimization which is valuable for code
210          --  optimization, and also for generation of compiler warnings, but
211          --  these are being turned off anyway, and CodePeer understands
212          --  things more clearly if references are not optimized in this way.
213
214          Warning_Mode  := Suppress;
215          Debug_Flag_MM := True;
216
217          --  Set normal RM validity checking, and checking of IN OUT parameters
218          --  (this might give CodePeer more useful checks to analyze, to be
219          --  confirmed???). All other validity checking is turned off, since
220          --  this can generate very complex trees that only confuse CodePeer
221          --  and do not bring enough useful info.
222
223          Reset_Validity_Check_Options;
224          Validity_Check_Default       := True;
225          Validity_Check_In_Out_Params := True;
226          Validity_Check_In_Params     := True;
227
228          --  Turn off style check options since we are not interested in any
229          --  front-end warnings when we are getting CodePeer output.
230
231          Reset_Style_Check_Options;
232       end if;
233
234       --  Set Configurable_Run_Time mode if system.ads flag set
235
236       if Targparm.Configurable_Run_Time_On_Target or Debug_Flag_YY then
237          Configurable_Run_Time_Mode := True;
238       end if;
239
240       --  Set -gnatR3m mode if debug flag A set
241
242       if Debug_Flag_AA then
243          Back_Annotate_Rep_Info := True;
244          List_Representation_Info := 1;
245          List_Representation_Info_Mechanisms := True;
246       end if;
247
248       --  Force Target_Strict_Alignment true if debug flag -gnatd.a is set
249
250       if Debug_Flag_Dot_A then
251          Ttypes.Target_Strict_Alignment := True;
252       end if;
253
254       --  Disable static allocation of dispatch tables if -gnatd.t or if layout
255       --  is enabled. The front end's layout phase currently treats types that
256       --  have discriminant-dependent arrays as not being static even when a
257       --  discriminant constraint on the type is static, and this leads to
258       --  problems with subtypes of type Ada.Tags.Dispatch_Table_Wrapper. ???
259
260       if Debug_Flag_Dot_T or else Frontend_Layout_On_Target then
261          Static_Dispatch_Tables := False;
262       end if;
263
264       --  Flip endian mode if -gnatd8 set
265
266       if Debug_Flag_8 then
267          Ttypes.Bytes_Big_Endian := not Ttypes.Bytes_Big_Endian;
268       end if;
269
270       --  Deal with forcing OpenVMS switches True if debug flag M is set, but
271       --  record the setting of Targparm.Open_VMS_On_Target in True_VMS_Target
272       --  before doing this, so we know if we are in real OpenVMS or not!
273
274       Opt.True_VMS_Target := Targparm.OpenVMS_On_Target;
275
276       if Debug_Flag_M then
277          Targparm.OpenVMS_On_Target := True;
278          Hostparm.OpenVMS := True;
279       end if;
280
281       --  Activate front end layout if debug flag -gnatdF is set
282
283       if Debug_Flag_FF then
284          Targparm.Frontend_Layout_On_Target := True;
285       end if;
286
287       --  Set and check exception mechnism
288
289       if Targparm.ZCX_By_Default_On_Target then
290          if Targparm.GCC_ZCX_Support_On_Target then
291             Exception_Mechanism := Back_End_Exceptions;
292          else
293             Osint.Fail ("Zero Cost Exceptions not supported on this target");
294          end if;
295       end if;
296
297       --  Set proper status for overflow checks. We turn on overflow checks
298       --  if -gnatp was not specified, and either -gnato is set or the back
299       --  end takes care of overflow checks. Otherwise we suppress overflow
300       --  checks by default (since front end checks are expensive).
301
302       if not Opt.Suppress_Checks
303         and then (Opt.Enable_Overflow_Checks
304                     or else
305                       (Targparm.Backend_Divide_Checks_On_Target
306                         and
307                        Targparm.Backend_Overflow_Checks_On_Target))
308       then
309          Suppress_Options (Overflow_Check) := False;
310       else
311          Suppress_Options (Overflow_Check) := True;
312       end if;
313    end Adjust_Global_Switches;
314
315    --------------------
316    -- Check_Bad_Body --
317    --------------------
318
319    procedure Check_Bad_Body is
320       Sname   : Unit_Name_Type;
321       Src_Ind : Source_File_Index;
322       Fname   : File_Name_Type;
323
324       procedure Bad_Body_Error (Msg : String);
325       --  Issue message for bad body found
326
327       --------------------
328       -- Bad_Body_Error --
329       --------------------
330
331       procedure Bad_Body_Error (Msg : String) is
332       begin
333          Error_Msg_N (Msg, Main_Unit_Node);
334          Error_Msg_File_1 := Fname;
335          Error_Msg_N ("remove incorrect body in file{!", Main_Unit_Node);
336       end Bad_Body_Error;
337
338       --  Start of processing for Check_Bad_Body
339
340    begin
341       --  Nothing to do if we are only checking syntax, because we don't know
342       --  enough to know if we require or forbid a body in this case.
343
344       if Operating_Mode = Check_Syntax then
345          return;
346       end if;
347
348       --  Check for body not allowed
349
350       if (Main_Kind = N_Package_Declaration
351            and then not Body_Required (Main_Unit_Node))
352         or else (Main_Kind = N_Generic_Package_Declaration
353                   and then not Body_Required (Main_Unit_Node))
354         or else Main_Kind = N_Package_Renaming_Declaration
355         or else Main_Kind = N_Subprogram_Renaming_Declaration
356         or else Nkind (Original_Node (Unit (Main_Unit_Node)))
357                          in N_Generic_Instantiation
358       then
359          Sname := Unit_Name (Main_Unit);
360
361          --  If we do not already have a body name, then get the body name
362          --  (but how can we have a body name here ???)
363
364          if not Is_Body_Name (Sname) then
365             Sname := Get_Body_Name (Sname);
366          end if;
367
368          Fname := Get_File_Name (Sname, Subunit => False);
369          Src_Ind := Load_Source_File (Fname);
370
371          --  Case where body is present and it is not a subunit. Exclude
372          --  the subunit case, because it has nothing to do with the
373          --  package we are compiling. It is illegal for a child unit and a
374          --  subunit with the same expanded name (RM 10.2(9)) to appear
375          --  together in a partition, but there is nothing to stop a
376          --  compilation environment from having both, and the test here
377          --  simply allows that. If there is an attempt to include both in
378          --  a partition, this is diagnosed at bind time. In Ada 83 mode
379          --  this is not a warning case.
380
381          --  Note: if weird file names are being used, we can have
382          --  situation where the file name that supposedly contains body,
383          --  in fact contains a spec, or we can't tell what it contains.
384          --  Skip the error message in these cases.
385
386          --  Also ignore body that is nothing but pragma No_Body; (that's the
387          --  whole point of this pragma, to be used this way and to cause the
388          --  body file to be ignored in this context).
389
390          if Src_Ind /= No_Source_File
391            and then Get_Expected_Unit_Type (Fname) = Expect_Body
392            and then not Source_File_Is_Subunit (Src_Ind)
393            and then not Source_File_Is_No_Body (Src_Ind)
394          then
395             Errout.Finalize (Last_Call => False);
396
397             Error_Msg_Unit_1 := Sname;
398
399             --  Ada 83 case of a package body being ignored. This is not an
400             --  error as far as the Ada 83 RM is concerned, but it is almost
401             --  certainly not what is wanted so output a warning. Give this
402             --  message only if there were no errors, since otherwise it may
403             --  be incorrect (we may have misinterpreted a junk spec as not
404             --  needing a body when it really does).
405
406             if Main_Kind = N_Package_Declaration
407               and then Ada_Version = Ada_83
408               and then Operating_Mode = Generate_Code
409               and then Distribution_Stub_Mode /= Generate_Caller_Stub_Body
410               and then not Compilation_Errors
411             then
412                Error_Msg_N
413                  ("package $$ does not require a body?", Main_Unit_Node);
414                Error_Msg_File_1 := Fname;
415                Error_Msg_N ("body in file{? will be ignored", Main_Unit_Node);
416
417                --  Ada 95 cases of a body file present when no body is
418                --  permitted. This we consider to be an error.
419
420             else
421                --  For generic instantiations, we never allow a body
422
423                if Nkind (Original_Node (Unit (Main_Unit_Node)))
424                in N_Generic_Instantiation
425                then
426                   Bad_Body_Error
427                     ("generic instantiation for $$ does not allow a body");
428
429                   --  A library unit that is a renaming never allows a body
430
431                elsif Main_Kind in N_Renaming_Declaration then
432                   Bad_Body_Error
433                     ("renaming declaration for $$ does not allow a body!");
434
435                   --  Remaining cases are packages and generic packages. Here
436                   --  we only do the test if there are no previous errors,
437                   --  because if there are errors, they may lead us to
438                   --  incorrectly believe that a package does not allow a body
439                   --  when in fact it does.
440
441                elsif not Compilation_Errors then
442                   if Main_Kind = N_Package_Declaration then
443                      Bad_Body_Error
444                        ("package $$ does not allow a body!");
445
446                   elsif Main_Kind = N_Generic_Package_Declaration then
447                      Bad_Body_Error
448                        ("generic package $$ does not allow a body!");
449                   end if;
450                end if;
451
452             end if;
453          end if;
454       end if;
455    end Check_Bad_Body;
456
457    --------------------
458    -- Check_Rep_Info --
459    --------------------
460
461    procedure Check_Rep_Info is
462    begin
463       if List_Representation_Info /= 0
464         or else List_Representation_Info_Mechanisms
465       then
466          Set_Standard_Error;
467          Write_Eol;
468          Write_Str
469            ("cannot generate representation information, no code generated");
470          Write_Eol;
471          Write_Eol;
472          Set_Standard_Output;
473       end if;
474    end Check_Rep_Info;
475
476    -------------------------
477    -- Check_Library_Items --
478    -------------------------
479
480    --  Walk_Library_Items has plenty of assertions, so all we need to do is
481    --  call it, just for these assertions, not actually doing anything else.
482
483    procedure Check_Library_Items is
484
485       procedure Action (Item : Node_Id);
486       --  Action passed to Walk_Library_Items to do nothing
487
488       ------------
489       -- Action --
490       ------------
491
492       procedure Action (Item : Node_Id) is
493       begin
494          null;
495       end Action;
496
497       procedure Walk is new Sem.Walk_Library_Items (Action);
498
499    --  Start of processing for Check_Library_Items
500
501    begin
502       Walk;
503    end Check_Library_Items;
504
505 --  Start of processing for Gnat1drv
506
507 begin
508    --  This inner block is set up to catch assertion errors and constraint
509    --  errors. Since the code for handling these errors can cause another
510    --  exception to be raised (namely Unrecoverable_Error), we need two
511    --  nested blocks, so that the outer one handles unrecoverable error.
512
513    begin
514       --  Initialize all packages. For the most part, these initialization
515       --  calls can be made in any order. Exceptions are as follows:
516
517       --  Lib.Initialize need to be called before Scan_Compiler_Arguments,
518       --  because it initializes a table filled by Scan_Compiler_Arguments.
519
520       Osint.Initialize;
521       Fmap.Reset_Tables;
522       Lib.Initialize;
523       Lib.Xref.Initialize;
524       Scan_Compiler_Arguments;
525       Osint.Add_Default_Search_Dirs;
526
527       Nlists.Initialize;
528       Sinput.Initialize;
529       Sem.Initialize;
530       Csets.Initialize;
531       Uintp.Initialize;
532       Urealp.Initialize;
533       Errout.Initialize;
534       Namet.Initialize;
535       Snames.Initialize;
536       Stringt.Initialize;
537       Inline.Initialize;
538       Par_SCO.Initialize;
539       Sem_Ch8.Initialize;
540       Sem_Ch12.Initialize;
541       Sem_Ch13.Initialize;
542       Sem_Elim.Initialize;
543       Sem_Eval.Initialize;
544       Sem_Type.Init_Interp_Tables;
545
546       --  Acquire target parameters from system.ads (source of package System)
547
548       declare
549          use Sinput;
550
551          S : Source_File_Index;
552          N : File_Name_Type;
553
554       begin
555          Name_Buffer (1 .. 10) := "system.ads";
556          Name_Len := 10;
557          N := Name_Find;
558          S := Load_Source_File (N);
559
560          if S = No_Source_File then
561             Write_Line
562               ("fatal error, run-time library not installed correctly");
563             Write_Line
564               ("cannot locate file system.ads");
565             raise Unrecoverable_Error;
566
567          --  Remember source index of system.ads (which was read successfully)
568
569          else
570             System_Source_File_Index := S;
571          end if;
572
573          Targparm.Get_Target_Parameters
574            (System_Text  => Source_Text  (S),
575             Source_First => Source_First (S),
576             Source_Last  => Source_Last  (S));
577
578          --  Acquire configuration pragma information from Targparm
579
580          Restrict.Restrictions := Targparm.Restrictions_On_Target;
581       end;
582
583       Adjust_Global_Switches;
584
585       --  Output copyright notice if full list mode unless we have a list
586       --  file, in which case we defer this so that it is output in the file
587
588       if (Verbose_Mode or else (Full_List and then Full_List_File_Name = null))
589         and then not Debug_Flag_7
590       then
591          Write_Eol;
592          Write_Str ("GNAT ");
593          Write_Str (Gnat_Version_String);
594          Write_Eol;
595          Write_Str ("Copyright 1992-" &
596                     Current_Year &
597                     ", Free Software Foundation, Inc.");
598          Write_Eol;
599       end if;
600
601       --  Check we do not have more than one source file, this happens only in
602       --  the case where the driver is called directly, it cannot happen when
603       --  gnat1 is invoked from gcc in the normal case.
604
605       if Osint.Number_Of_Files /= 1 then
606          Usage;
607          Write_Eol;
608          Osint.Fail ("you must provide one source file");
609
610       elsif Usage_Requested then
611          Usage;
612       end if;
613
614       Original_Operating_Mode := Operating_Mode;
615       Frontend;
616
617       --  Exit with errors if the main source could not be parsed
618
619       if Sinput.Main_Source_File = No_Source_File then
620          Errout.Finalize (Last_Call => True);
621          Errout.Output_Messages;
622          Exit_Program (E_Errors);
623       end if;
624
625       Main_Unit_Node := Cunit (Main_Unit);
626       Main_Kind := Nkind (Unit (Main_Unit_Node));
627       Check_Bad_Body;
628
629       --  Exit if compilation errors detected
630
631       Errout.Finalize (Last_Call => False);
632
633       if Compilation_Errors then
634          Treepr.Tree_Dump;
635          Sem_Ch13.Validate_Unchecked_Conversions;
636          Sem_Ch13.Validate_Address_Clauses;
637          Errout.Output_Messages;
638          Namet.Finalize;
639
640          --  Generate ALI file if specially requested
641
642          if Opt.Force_ALI_Tree_File then
643             Write_ALI (Object => False);
644             Tree_Gen;
645          end if;
646
647          Errout.Finalize (Last_Call => True);
648          Exit_Program (E_Errors);
649       end if;
650
651       --  Set Generate_Code on main unit and its spec. We do this even if are
652       --  not generating code, since Lib-Writ uses this to determine which
653       --  units get written in the ali file.
654
655       Set_Generate_Code (Main_Unit);
656
657       --  If we have a corresponding spec, and it comes from source
658       --  or it is not a generated spec for a child subprogram body,
659       --  then we need object code for the spec unit as well.
660
661       if Nkind (Unit (Main_Unit_Node)) in N_Unit_Body
662         and then not Acts_As_Spec (Main_Unit_Node)
663       then
664          if Nkind (Unit (Main_Unit_Node)) = N_Subprogram_Body
665            and then not Comes_From_Source (Library_Unit (Main_Unit_Node))
666          then
667             null;
668          else
669             Set_Generate_Code
670               (Get_Cunit_Unit_Number (Library_Unit (Main_Unit_Node)));
671          end if;
672       end if;
673
674       --  Case of no code required to be generated, exit indicating no error
675
676       if Original_Operating_Mode = Check_Syntax then
677          Treepr.Tree_Dump;
678          Errout.Finalize (Last_Call => True);
679          Errout.Output_Messages;
680          Tree_Gen;
681          Namet.Finalize;
682          Check_Rep_Info;
683
684          --  Use a goto instead of calling Exit_Program so that finalization
685          --  occurs normally.
686
687          goto End_Of_Program;
688
689       elsif Original_Operating_Mode = Check_Semantics then
690          Back_End_Mode := Declarations_Only;
691
692       --  All remaining cases are cases in which the user requested that code
693       --  be generated (i.e. no -gnatc or -gnats switch was used). Check if
694       --  we can in fact satisfy this request.
695
696       --  Cannot generate code if someone has turned off code generation for
697       --  any reason at all. We will try to figure out a reason below.
698
699       elsif Operating_Mode /= Generate_Code then
700          Back_End_Mode := Skip;
701
702       --  We can generate code for a subprogram body unless there were missing
703       --  subunits. Note that we always generate code for all generic units (a
704       --  change from some previous versions of GNAT).
705
706       elsif Main_Kind = N_Subprogram_Body
707         and then not Subunits_Missing
708       then
709          Back_End_Mode := Generate_Object;
710
711       --  We can generate code for a package body unless there are subunits
712       --  missing (note that we always generate code for generic units, which
713       --  is a change from some earlier versions of GNAT).
714
715       elsif Main_Kind = N_Package_Body
716         and then not Subunits_Missing
717       then
718          Back_End_Mode := Generate_Object;
719
720       --  We can generate code for a package declaration or a subprogram
721       --  declaration only if it does not required a body.
722
723       elsif (Main_Kind = N_Package_Declaration
724                or else
725              Main_Kind = N_Subprogram_Declaration)
726         and then
727           (not Body_Required (Main_Unit_Node)
728              or else
729            Distribution_Stub_Mode = Generate_Caller_Stub_Body)
730       then
731          Back_End_Mode := Generate_Object;
732
733       --  We can generate code for a generic package declaration of a generic
734       --  subprogram declaration only if does not require a body.
735
736       elsif (Main_Kind = N_Generic_Package_Declaration
737                or else
738              Main_Kind = N_Generic_Subprogram_Declaration)
739         and then not Body_Required (Main_Unit_Node)
740       then
741          Back_End_Mode := Generate_Object;
742
743       --  Compilation units that are renamings do not require bodies,
744       --  so we can generate code for them.
745
746       elsif Main_Kind = N_Package_Renaming_Declaration
747         or else Main_Kind = N_Subprogram_Renaming_Declaration
748       then
749          Back_End_Mode := Generate_Object;
750
751       --  Compilation units that are generic renamings do not require bodies
752       --  so we can generate code for them.
753
754       elsif Main_Kind in N_Generic_Renaming_Declaration then
755          Back_End_Mode := Generate_Object;
756
757       --  It's not an error to generate SCIL for e.g. a spec which has a body
758
759       elsif CodePeer_Mode then
760          Back_End_Mode := Generate_Object;
761
762       --  In all other cases (specs which have bodies, generics, and bodies
763       --  where subunits are missing), we cannot generate code and we generate
764       --  a warning message. Note that generic instantiations are gone at this
765       --  stage since they have been replaced by their instances.
766
767       else
768          Back_End_Mode := Skip;
769       end if;
770
771       --  At this stage Back_End_Mode is set to indicate if the backend should
772       --  be called to generate code. If it is Skip, then code generation has
773       --  been turned off, even though code was requested by the original
774       --  command. This is not an error from the user point of view, but it is
775       --  an error from the point of view of the gcc driver, so we must exit
776       --  with an error status.
777
778       --  We generate an informative message (from the gcc point of view, it
779       --  is an error message, but from the users point of view this is not an
780       --  error, just a consequence of compiling something that cannot
781       --  generate code).
782
783       if Back_End_Mode = Skip then
784          Set_Standard_Error;
785          Write_Str ("cannot generate code for ");
786          Write_Str ("file ");
787          Write_Name (Unit_File_Name (Main_Unit));
788
789          if Subunits_Missing then
790             Write_Str (" (missing subunits)");
791             Write_Eol;
792             Write_Str ("to check parent unit");
793
794          elsif Main_Kind = N_Subunit then
795             Write_Str (" (subunit)");
796             Write_Eol;
797             Write_Str ("to check subunit");
798
799          elsif Main_Kind = N_Subprogram_Declaration then
800             Write_Str (" (subprogram spec)");
801             Write_Eol;
802             Write_Str ("to check subprogram spec");
803
804          --  Generic package body in GNAT implementation mode
805
806          elsif Main_Kind = N_Package_Body and then GNAT_Mode then
807             Write_Str (" (predefined generic)");
808             Write_Eol;
809             Write_Str ("to check predefined generic");
810
811          --  Only other case is a package spec
812
813          else
814             Write_Str (" (package spec)");
815             Write_Eol;
816             Write_Str ("to check package spec");
817          end if;
818
819          Write_Str (" for errors, use ");
820
821          if Hostparm.OpenVMS then
822             Write_Str ("/NOLOAD");
823          else
824             Write_Str ("-gnatc");
825          end if;
826
827          Write_Eol;
828          Set_Standard_Output;
829
830          Sem_Ch13.Validate_Unchecked_Conversions;
831          Sem_Ch13.Validate_Address_Clauses;
832          Errout.Finalize (Last_Call => True);
833          Errout.Output_Messages;
834          Treepr.Tree_Dump;
835          Tree_Gen;
836          Write_ALI (Object => False);
837          Namet.Finalize;
838          Check_Rep_Info;
839
840          --  Exit program with error indication, to kill object file
841
842          Exit_Program (E_No_Code);
843       end if;
844
845       --  In -gnatc mode, we only do annotation if -gnatt or -gnatR is also
846       --  set as indicated by Back_Annotate_Rep_Info being set to True.
847
848       --  We don't call for annotations on a subunit, because to process those
849       --  the back-end requires that the parent(s) be properly compiled.
850
851       --  Annotation is suppressed for targets where front-end layout is
852       --  enabled, because the front end determines representations.
853
854       --  Annotation is also suppressed in the case of compiling for
855       --  a VM, since representations are largely symbolic there.
856
857       if Back_End_Mode = Declarations_Only
858         and then (not (Back_Annotate_Rep_Info or Generate_SCIL)
859                    or else Main_Kind = N_Subunit
860                    or else Targparm.Frontend_Layout_On_Target
861                    or else Targparm.VM_Target /= No_VM)
862       then
863          Sem_Ch13.Validate_Unchecked_Conversions;
864          Sem_Ch13.Validate_Address_Clauses;
865          Errout.Finalize (Last_Call => True);
866          Errout.Output_Messages;
867          Write_ALI (Object => False);
868          Tree_Dump;
869          Tree_Gen;
870          Namet.Finalize;
871          Check_Rep_Info;
872          return;
873       end if;
874
875       --  Ensure that we properly register a dependency on system.ads, since
876       --  even if we do not semantically depend on this, Targparm has read
877       --  system parameters from the system.ads file.
878
879       Lib.Writ.Ensure_System_Dependency;
880
881       --  Add dependencies, if any, on preprocessing data file and on
882       --  preprocessing definition file(s).
883
884       Prepcomp.Add_Dependencies;
885
886       --  Back end needs to explicitly unlock tables it needs to touch
887
888       Atree.Lock;
889       Elists.Lock;
890       Fname.UF.Lock;
891       Inline.Lock;
892       Lib.Lock;
893       Nlists.Lock;
894       Sem.Lock;
895       Sinput.Lock;
896       Namet.Lock;
897       Stringt.Lock;
898
899       --  ???Check_Library_Items under control of a debug flag, because it
900       --  currently does not work if the -gnatn switch (back end inlining) is
901       --  used.
902
903       if Debug_Flag_Dot_WW then
904          Check_Library_Items;
905       end if;
906
907       --  Here we call the back end to generate the output code
908
909       Generating_Code := True;
910       Back_End.Call_Back_End (Back_End_Mode);
911
912       --  Once the backend is complete, we unlock the names table. This call
913       --  allows a few extra entries, needed for example for the file name for
914       --  the library file output.
915
916       Namet.Unlock;
917
918       --  Validate unchecked conversions (using the values for size and
919       --  alignment annotated by the backend where possible).
920
921       Sem_Ch13.Validate_Unchecked_Conversions;
922
923       --  Validate address clauses (again using alignment values annotated
924       --  by the backend where possible).
925
926       Sem_Ch13.Validate_Address_Clauses;
927
928       --  Now we complete output of errors, rep info and the tree info. These
929       --  are delayed till now, since it is perfectly possible for gigi to
930       --  generate errors, modify the tree (in particular by setting flags
931       --  indicating that elaboration is required, and also to back annotate
932       --  representation information for List_Rep_Info.
933
934       Errout.Finalize (Last_Call => True);
935       Errout.Output_Messages;
936       List_Rep_Info;
937
938       --  Only write the library if the backend did not generate any error
939       --  messages. Otherwise signal errors to the driver program so that
940       --  there will be no attempt to generate an object file.
941
942       if Compilation_Errors then
943          Treepr.Tree_Dump;
944          Exit_Program (E_Errors);
945       end if;
946
947       Write_ALI (Object => (Back_End_Mode = Generate_Object));
948
949       --  Generate the ASIS tree after writing the ALI file, since in ASIS
950       --  mode, Write_ALI may in fact result in further tree decoration from
951       --  the original tree file. Note that we dump the tree just before
952       --  generating it, so that the dump will exactly reflect what is written
953       --  out.
954
955       Treepr.Tree_Dump;
956       Tree_Gen;
957
958       --  Finalize name table and we are all done
959
960       Namet.Finalize;
961
962    exception
963       --  Handle fatal internal compiler errors
964
965       when Rtsfind.RE_Not_Available =>
966          Comperr.Compiler_Abort ("RE_Not_Available");
967
968       when System.Assertions.Assert_Failure =>
969          Comperr.Compiler_Abort ("Assert_Failure");
970
971       when Constraint_Error =>
972          Comperr.Compiler_Abort ("Constraint_Error");
973
974       when Program_Error =>
975          Comperr.Compiler_Abort ("Program_Error");
976
977       when Storage_Error =>
978
979          --  Assume this is a bug. If it is real, the message will in any case
980          --  say Storage_Error, giving a strong hint!
981
982          Comperr.Compiler_Abort ("Storage_Error");
983    end;
984
985    <<End_Of_Program>>
986    null;
987
988    --  The outer exception handles an unrecoverable error
989
990 exception
991    when Unrecoverable_Error =>
992       Errout.Finalize (Last_Call => True);
993       Errout.Output_Messages;
994
995       Set_Standard_Error;
996       Write_Str ("compilation abandoned");
997       Write_Eol;
998
999       Set_Standard_Output;
1000       Source_Dump;
1001       Tree_Dump;
1002       Exit_Program (E_Errors);
1003
1004 end Gnat1drv;