OSDN Git Service

2007-09-26 Thomas Quinot <quinot@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / restrict.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             R E S T R I C T                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2007, 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 Casing;   use Casing;
28 with Errout;   use Errout;
29 with Fname;    use Fname;
30 with Fname.UF; use Fname.UF;
31 with Lib;      use Lib;
32 with Opt;      use Opt;
33 with Sinfo;    use Sinfo;
34 with Sinput;   use Sinput;
35 with Snames;   use Snames;
36 with Uname;    use Uname;
37
38 package body Restrict is
39
40    Restricted_Profile_Result : Boolean := False;
41    --  This switch memoizes the result of Restricted_Profile function
42    --  calls for improved efficiency. Its setting is valid only if
43    --  Restricted_Profile_Cached is True. Note that if this switch
44    --  is ever set True, it need never be turned off again.
45
46    Restricted_Profile_Cached : Boolean := False;
47    --  This flag is set to True if the Restricted_Profile_Result
48    --  contains the correct cached result of Restricted_Profile calls.
49
50    -----------------------
51    -- Local Subprograms --
52    -----------------------
53
54    procedure Restriction_Msg (Msg : String; R : String; N : Node_Id);
55    --  Output error message at node N with given text, replacing the
56    --  '%' in the message with the name of the restriction given as R,
57    --  cased according to the current identifier casing. We do not use
58    --  the normal insertion mechanism, since this requires an entry
59    --  in the Names table, and this table will be locked if we are
60    --  generating a message from gigi.
61
62    function Same_Unit (U1, U2 : Node_Id) return Boolean;
63    --  Returns True iff U1 and U2 represent the same library unit. Used for
64    --  handling of No_Dependence => Unit restriction case.
65
66    function Suppress_Restriction_Message (N : Node_Id) return Boolean;
67    --  N is the node for a possible restriction violation message, but
68    --  the message is to be suppressed if this is an internal file and
69    --  this file is not the main unit.
70
71    -------------------
72    -- Abort_Allowed --
73    -------------------
74
75    function Abort_Allowed return Boolean is
76    begin
77       if Restrictions.Set (No_Abort_Statements)
78         and then Restrictions.Set (Max_Asynchronous_Select_Nesting)
79         and then Restrictions.Value (Max_Asynchronous_Select_Nesting) = 0
80       then
81          return False;
82       else
83          return True;
84       end if;
85    end Abort_Allowed;
86
87    -------------------------
88    -- Check_Compiler_Unit --
89    -------------------------
90
91    procedure Check_Compiler_Unit (N : Node_Id) is
92    begin
93       if Is_Compiler_Unit (Get_Source_Unit (N)) then
94          Error_Msg_N ("use of construct not allowed in compiler", N);
95       end if;
96    end Check_Compiler_Unit;
97
98    ------------------------------------
99    -- Check_Elaboration_Code_Allowed --
100    ------------------------------------
101
102    procedure Check_Elaboration_Code_Allowed (N : Node_Id) is
103    begin
104       --  Avoid calling Namet.Unlock/Lock except when there is an error.
105       --  Even in the error case it is a bit dubious, either gigi needs
106       --  the table locked or it does not! ???
107
108       if Restrictions.Set (No_Elaboration_Code)
109         and then not Suppress_Restriction_Message (N)
110       then
111          Namet.Unlock;
112          Check_Restriction (No_Elaboration_Code, N);
113          Namet.Lock;
114       end if;
115    end Check_Elaboration_Code_Allowed;
116
117    ----------------------------------
118    -- Check_No_Implicit_Heap_Alloc --
119    ----------------------------------
120
121    procedure Check_No_Implicit_Heap_Alloc (N : Node_Id) is
122    begin
123       Check_Restriction (No_Implicit_Heap_Allocations, N);
124    end Check_No_Implicit_Heap_Alloc;
125
126    ---------------------------
127    -- Check_Restricted_Unit --
128    ---------------------------
129
130    procedure Check_Restricted_Unit (U : Unit_Name_Type; N : Node_Id) is
131    begin
132       if Suppress_Restriction_Message (N) then
133          return;
134
135       elsif Is_Spec_Name (U) then
136          declare
137             Fnam : constant File_Name_Type :=
138                      Get_File_Name (U, Subunit => False);
139
140          begin
141             --  Get file name
142
143             Get_Name_String (Fnam);
144
145             --  Nothing to do if name not at least 5 characters long ending
146             --  in .ads or .adb extension, which we strip.
147
148             if Name_Len < 5
149               or else (Name_Buffer (Name_Len - 3 .. Name_Len) /= ".ads"
150                          and then
151                        Name_Buffer (Name_Len - 4 .. Name_Len) /= ".adb")
152             then
153                return;
154             end if;
155
156             --  Strip extension and pad to eight characters
157
158             Name_Len := Name_Len - 4;
159             while Name_Len < 8 loop
160                Name_Len := Name_Len + 1;
161                Name_Buffer (Name_Len) := ' ';
162             end loop;
163
164             --  If predefined unit, check the list of restricted units
165
166             if Is_Predefined_File_Name (Fnam) then
167                for J in Unit_Array'Range loop
168                   if Name_Len = 8
169                     and then Name_Buffer (1 .. 8) = Unit_Array (J).Filenm
170                   then
171                      Check_Restriction (Unit_Array (J).Res_Id, N);
172                   end if;
173                end loop;
174
175                --  If not predefied unit, then one special check still remains.
176                --  GNAT.Current_Exception is not allowed if we have restriction
177                --  No_Exception_Propagation active.
178
179             else
180                if Name_Buffer (1 .. 8) = "g-curexc" then
181                   Check_Restriction (No_Exception_Propagation, N);
182                end if;
183             end if;
184          end;
185       end if;
186    end Check_Restricted_Unit;
187
188    -----------------------
189    -- Check_Restriction --
190    -----------------------
191
192    procedure Check_Restriction
193      (R : Restriction_Id;
194       N : Node_Id;
195       V : Uint := Uint_Minus_1)
196    is
197       Rimage : constant String := Restriction_Id'Image (R);
198
199       VV : Integer;
200       --  V converted to integer form. If V is greater than Integer'Last,
201       --  it is reset to minus 1 (unknown value).
202
203       procedure Update_Restrictions (Info : in out Restrictions_Info);
204       --  Update violation information in Info.Violated and Info.Count
205
206       -------------------------
207       -- Update_Restrictions --
208       -------------------------
209
210       procedure Update_Restrictions (Info : in out Restrictions_Info) is
211       begin
212          --  If not violated, set as violated now
213
214          if not Info.Violated (R) then
215             Info.Violated (R) := True;
216
217             if R in All_Parameter_Restrictions then
218                if VV < 0 then
219                   Info.Unknown (R) := True;
220                   Info.Count (R) := 1;
221                else
222                   Info.Count (R) := VV;
223                end if;
224             end if;
225
226          --  Otherwise if violated already and a parameter restriction,
227          --  update count by maximizing or summing depending on restriction.
228
229          elsif R in All_Parameter_Restrictions then
230
231             --  If new value is unknown, result is unknown
232
233             if VV < 0 then
234                Info.Unknown (R) := True;
235
236             --  If checked by maximization, do maximization
237
238             elsif R in Checked_Max_Parameter_Restrictions then
239                Info.Count (R) := Integer'Max (Info.Count (R), VV);
240
241             --  If checked by adding, do add, checking for overflow
242
243             elsif R in Checked_Add_Parameter_Restrictions then
244                declare
245                   pragma Unsuppress (Overflow_Check);
246                begin
247                   Info.Count (R) := Info.Count (R) + VV;
248                exception
249                   when Constraint_Error =>
250                      Info.Count (R) := Integer'Last;
251                      Info.Unknown (R) := True;
252                end;
253
254             --  Should not be able to come here, known counts should only
255             --  occur for restrictions that are Checked_max or Checked_Sum.
256
257             else
258                raise Program_Error;
259             end if;
260          end if;
261       end Update_Restrictions;
262
263    --  Start of processing for Check_Restriction
264
265    begin
266       if UI_Is_In_Int_Range (V) then
267          VV := Integer (UI_To_Int (V));
268       else
269          VV := -1;
270       end if;
271
272       --  Count can only be specified in the checked val parameter case
273
274       pragma Assert (VV < 0 or else R in Checked_Val_Parameter_Restrictions);
275
276       --  Nothing to do if value of zero specified for parameter restriction
277
278       if VV = 0 then
279          return;
280       end if;
281
282       --  Update current restrictions
283
284       Update_Restrictions (Restrictions);
285
286       --  If in main extended unit, update main restrictions as well
287
288       if Current_Sem_Unit = Main_Unit
289         or else In_Extended_Main_Source_Unit (N)
290       then
291          Update_Restrictions (Main_Restrictions);
292       end if;
293
294       --  Nothing to do if restriction message suppressed
295
296       if Suppress_Restriction_Message (N) then
297          null;
298
299       --  If restriction not set, nothing to do
300
301       elsif not Restrictions.Set (R) then
302          null;
303
304       --  Here if restriction set, check for violation (either this is a
305       --  Boolean restriction, or a parameter restriction with a value of
306       --  zero and an unknown count, or a parameter restriction with a
307       --  known value that exceeds the restriction count).
308
309       elsif R in All_Boolean_Restrictions
310         or else (Restrictions.Unknown (R)
311                    and then Restrictions.Value (R) = 0)
312         or else Restrictions.Count (R) > Restrictions.Value (R)
313       then
314          Error_Msg_Sloc := Restrictions_Loc (R);
315
316          --  If we have a location for the Restrictions pragma, output it
317
318          if Error_Msg_Sloc > No_Location
319            or else Error_Msg_Sloc = System_Location
320          then
321             if Restriction_Warnings (R) then
322                Restriction_Msg ("|violation of restriction %#?", Rimage, N);
323             else
324                Restriction_Msg ("|violation of restriction %#", Rimage, N);
325             end if;
326
327          --  Otherwise we have the case of an implicit restriction
328          --  (e.g. a restriction implicitly set by another pragma)
329
330          else
331             Restriction_Msg
332               ("|violation of implicit restriction %", Rimage, N);
333          end if;
334       end if;
335    end Check_Restriction;
336
337    -------------------------------------
338    -- Check_Restriction_No_Dependence --
339    -------------------------------------
340
341    procedure Check_Restriction_No_Dependence (U : Node_Id; Err : Node_Id) is
342       DU : Node_Id;
343
344    begin
345       for J in No_Dependence.First .. No_Dependence.Last loop
346          DU := No_Dependence.Table (J).Unit;
347
348          if Same_Unit (U, DU) then
349             Error_Msg_Sloc := Sloc (DU);
350             Error_Msg_Node_1 := DU;
351
352             if No_Dependence.Table (J).Warn then
353                Error_Msg
354                  ("?violation of restriction `No_Dependence '='> &`#",
355                   Sloc (Err));
356             else
357                Error_Msg
358                  ("|violation of restriction `No_Dependence '='> &`#",
359                   Sloc (Err));
360             end if;
361
362             return;
363          end if;
364       end loop;
365    end Check_Restriction_No_Dependence;
366
367    ----------------------------------------
368    -- Cunit_Boolean_Restrictions_Restore --
369    ----------------------------------------
370
371    procedure Cunit_Boolean_Restrictions_Restore
372      (R : Save_Cunit_Boolean_Restrictions)
373    is
374    begin
375       for J in Cunit_Boolean_Restrictions loop
376          Restrictions.Set (J) := R (J);
377       end loop;
378    end Cunit_Boolean_Restrictions_Restore;
379
380    -------------------------------------
381    -- Cunit_Boolean_Restrictions_Save --
382    -------------------------------------
383
384    function Cunit_Boolean_Restrictions_Save
385      return Save_Cunit_Boolean_Restrictions
386    is
387       R : Save_Cunit_Boolean_Restrictions;
388
389    begin
390       for J in Cunit_Boolean_Restrictions loop
391          R (J) := Restrictions.Set (J);
392          Restrictions.Set (J) := False;
393       end loop;
394
395       return R;
396    end Cunit_Boolean_Restrictions_Save;
397
398    ------------------------
399    -- Get_Restriction_Id --
400    ------------------------
401
402    function Get_Restriction_Id
403      (N : Name_Id) return Restriction_Id
404    is
405    begin
406       Get_Name_String (N);
407       Set_Casing (All_Upper_Case);
408
409       for J in All_Restrictions loop
410          declare
411             S : constant String := Restriction_Id'Image (J);
412          begin
413             if S = Name_Buffer (1 .. Name_Len) then
414                return J;
415             end if;
416          end;
417       end loop;
418
419       return Not_A_Restriction_Id;
420    end Get_Restriction_Id;
421
422    -------------------------------
423    -- No_Exception_Handlers_Set --
424    -------------------------------
425
426    function No_Exception_Handlers_Set return Boolean is
427    begin
428       return (No_Run_Time_Mode or else Configurable_Run_Time_Mode)
429         and then (Restrictions.Set (No_Exception_Handlers)
430                     or else
431                   Restrictions.Set (No_Exception_Propagation));
432    end No_Exception_Handlers_Set;
433
434    ----------------------------------
435    -- Process_Restriction_Synonyms --
436    ----------------------------------
437
438    --  Note: body of this function must be coordinated with list of
439    --  renaming declarations in System.Rident.
440
441    function Process_Restriction_Synonyms (N : Node_Id) return Name_Id
442    is
443       Old_Name : constant Name_Id := Chars (N);
444       New_Name : Name_Id;
445
446    begin
447       case Old_Name is
448          when Name_Boolean_Entry_Barriers =>
449             New_Name := Name_Simple_Barriers;
450
451          when Name_Max_Entry_Queue_Depth =>
452             New_Name := Name_Max_Entry_Queue_Length;
453
454          when Name_No_Dynamic_Interrupts =>
455             New_Name := Name_No_Dynamic_Attachment;
456
457          when Name_No_Requeue =>
458             New_Name := Name_No_Requeue_Statements;
459
460          when Name_No_Task_Attributes =>
461             New_Name := Name_No_Task_Attributes_Package;
462
463          when others =>
464             return Old_Name;
465       end case;
466
467       if Warn_On_Obsolescent_Feature then
468          Error_Msg_Name_1 := Old_Name;
469          Error_Msg_N ("restriction identifier % is obsolescent?", N);
470          Error_Msg_Name_1 := New_Name;
471          Error_Msg_N ("|use restriction identifier % instead", N);
472       end if;
473
474       return New_Name;
475    end Process_Restriction_Synonyms;
476
477    ------------------------
478    -- Restricted_Profile --
479    ------------------------
480
481    function Restricted_Profile return Boolean is
482    begin
483       if Restricted_Profile_Cached then
484          return Restricted_Profile_Result;
485
486       else
487          Restricted_Profile_Result := True;
488          Restricted_Profile_Cached := True;
489
490          declare
491             R : Restriction_Flags  renames Profile_Info (Restricted).Set;
492             V : Restriction_Values renames Profile_Info (Restricted).Value;
493          begin
494             for J in R'Range loop
495                if R (J)
496                  and then (Restrictions.Set (J) = False
497                              or else Restriction_Warnings (J)
498                              or else
499                                (J in All_Parameter_Restrictions
500                                   and then Restrictions.Value (J) > V (J)))
501                then
502                   Restricted_Profile_Result := False;
503                   exit;
504                end if;
505             end loop;
506
507             return Restricted_Profile_Result;
508          end;
509       end if;
510    end Restricted_Profile;
511
512    ------------------------
513    -- Restriction_Active --
514    ------------------------
515
516    function Restriction_Active (R : All_Restrictions) return Boolean is
517    begin
518       return Restrictions.Set (R) and then not Restriction_Warnings (R);
519    end Restriction_Active;
520
521    ---------------------
522    -- Restriction_Msg --
523    ---------------------
524
525    procedure Restriction_Msg (Msg : String; R : String; N : Node_Id) is
526       B : String (1 .. Msg'Length + 2 * R'Length + 1);
527       P : Natural := 1;
528
529    begin
530       Name_Buffer (1 .. R'Last) := R;
531       Name_Len := R'Length;
532       Set_Casing (Identifier_Casing (Get_Source_File_Index (Sloc (N))));
533
534       P := 0;
535       for J in Msg'Range loop
536          if Msg (J) = '%' then
537             P := P + 1;
538             B (P) := '`';
539
540             --  Put characters of image in message, quoting upper case letters
541
542             for J in 1 .. Name_Len loop
543                if Name_Buffer (J) in 'A' .. 'Z' then
544                   P := P + 1;
545                   B (P) := ''';
546                end if;
547
548                P := P + 1;
549                B (P) := Name_Buffer (J);
550             end loop;
551
552             P := P + 1;
553             B (P) := '`';
554
555          else
556             P := P + 1;
557             B (P) := Msg (J);
558          end if;
559       end loop;
560
561       Error_Msg_N (B (1 .. P), N);
562    end Restriction_Msg;
563
564    ---------------
565    -- Same_Unit --
566    ---------------
567
568    function Same_Unit (U1, U2 : Node_Id) return Boolean is
569    begin
570       if Nkind (U1) = N_Identifier then
571          return Nkind (U2) = N_Identifier and then Chars (U1) = Chars (U2);
572
573       elsif Nkind (U2) = N_Identifier then
574          return False;
575
576       elsif (Nkind (U1) = N_Selected_Component
577              or else Nkind (U1) = N_Expanded_Name)
578         and then
579           (Nkind (U2) = N_Selected_Component
580            or else Nkind (U2) = N_Expanded_Name)
581       then
582          return Same_Unit (Prefix (U1), Prefix (U2))
583            and then Same_Unit (Selector_Name (U1), Selector_Name (U2));
584       else
585          return False;
586       end if;
587    end Same_Unit;
588
589    ------------------------------
590    -- Set_Profile_Restrictions --
591    ------------------------------
592
593    procedure Set_Profile_Restrictions
594      (P    : Profile_Name;
595       N    : Node_Id;
596       Warn : Boolean)
597    is
598       R : Restriction_Flags  renames Profile_Info (P).Set;
599       V : Restriction_Values renames Profile_Info (P).Value;
600
601    begin
602       for J in R'Range loop
603          if R (J) then
604             declare
605                Already_Restricted : constant Boolean := Restriction_Active (J);
606
607             begin
608                --  Set the restriction
609
610                if J in All_Boolean_Restrictions then
611                   Set_Restriction (J, N);
612                else
613                   Set_Restriction (J, N, V (J));
614                end if;
615
616                --  Set warning flag, except that we do not set the warning
617                --  flag if the restriction was already active and this is
618                --  the warning case. That avoids a warning overriding a real
619                --  restriction, which should never happen.
620
621                if not (Warn and Already_Restricted) then
622                   Restriction_Warnings (J) := Warn;
623                end if;
624             end;
625          end if;
626       end loop;
627    end Set_Profile_Restrictions;
628
629    ---------------------
630    -- Set_Restriction --
631    ---------------------
632
633    --  Case of Boolean restriction
634
635    procedure Set_Restriction
636      (R : All_Boolean_Restrictions;
637       N : Node_Id)
638    is
639    begin
640       --  Restriction No_Elaboration_Code must be enforced on a unit by unit
641       --  basis. Hence, we avoid setting the restriction when processing an
642       --  unit which is not the main one being compiled (or its corresponding
643       --  spec). It can happen, for example, when processing an inlined body
644       --  (the package containing the inlined subprogram is analyzed,
645       --  including its pragma Restrictions).
646
647       --  This seems like a very nasty kludge??? This is not the only per unit
648       --  restriction why is this treated specially ???
649
650       if R = No_Elaboration_Code
651         and then Current_Sem_Unit /= Main_Unit
652         and then Cunit (Current_Sem_Unit) /= Library_Unit (Cunit (Main_Unit))
653       then
654          return;
655       end if;
656
657       Restrictions.Set (R) := True;
658
659       if Restricted_Profile_Cached and Restricted_Profile_Result then
660          null;
661       else
662          Restricted_Profile_Cached := False;
663       end if;
664
665       --  Set location, but preserve location of system
666       --  restriction for nice error msg with run time name
667
668       if Restrictions_Loc (R) /= System_Location then
669          Restrictions_Loc (R) := Sloc (N);
670       end if;
671
672       --  Record the restriction if we are in the main unit, or in the extended
673       --  main unit. The reason that we test separately for Main_Unit is that
674       --  gnat.adc is processed with Current_Sem_Unit = Main_Unit, but nodes in
675       --  gnat.adc do not appear to be in the extended main source unit (they
676       --  probably should do ???)
677
678       if Current_Sem_Unit = Main_Unit
679         or else In_Extended_Main_Source_Unit (N)
680       then
681          if not Restriction_Warnings (R) then
682             Main_Restrictions.Set (R) := True;
683          end if;
684       end if;
685    end Set_Restriction;
686
687    --  Case of parameter restriction
688
689    procedure Set_Restriction
690      (R : All_Parameter_Restrictions;
691       N : Node_Id;
692       V : Integer)
693    is
694    begin
695       if Restricted_Profile_Cached and Restricted_Profile_Result then
696          null;
697       else
698          Restricted_Profile_Cached := False;
699       end if;
700
701       if Restrictions.Set (R) then
702          if V < Restrictions.Value (R) then
703             Restrictions.Value (R) := V;
704             Restrictions_Loc (R) := Sloc (N);
705          end if;
706
707       else
708          Restrictions.Set (R) := True;
709          Restrictions.Value (R) := V;
710          Restrictions_Loc (R) := Sloc (N);
711       end if;
712
713       --  Record the restriction if we are in the main unit,
714       --  or in the extended main unit. The reason that we
715       --  test separately for Main_Unit is that gnat.adc is
716       --  processed with Current_Sem_Unit = Main_Unit, but
717       --  nodes in gnat.adc do not appear to be the extended
718       --  main source unit (they probably should do ???)
719
720       if Current_Sem_Unit = Main_Unit
721         or else In_Extended_Main_Source_Unit (N)
722       then
723          if Main_Restrictions.Set (R) then
724             if V < Main_Restrictions.Value (R) then
725                Main_Restrictions.Value (R) := V;
726             end if;
727
728          elsif not Restriction_Warnings (R) then
729             Main_Restrictions.Set (R) := True;
730             Main_Restrictions.Value (R) := V;
731          end if;
732       end if;
733    end Set_Restriction;
734
735    -----------------------------------
736    -- Set_Restriction_No_Dependence --
737    -----------------------------------
738
739    procedure Set_Restriction_No_Dependence
740      (Unit : Node_Id;
741       Warn : Boolean)
742    is
743    begin
744       --  Loop to check for duplicate entry
745
746       for J in No_Dependence.First .. No_Dependence.Last loop
747
748          --  Case of entry already in table
749
750          if Same_Unit (Unit, No_Dependence.Table (J).Unit) then
751
752             --  Error has precedence over warning
753
754             if not Warn then
755                No_Dependence.Table (J).Warn := False;
756             end if;
757
758             return;
759          end if;
760       end loop;
761
762       --  Entry is not currently in table
763
764       No_Dependence.Append ((Unit, Warn));
765    end Set_Restriction_No_Dependence;
766
767    ----------------------------------
768    -- Suppress_Restriction_Message --
769    ----------------------------------
770
771    function Suppress_Restriction_Message (N : Node_Id) return Boolean is
772    begin
773       --  We only output messages for the extended main source unit
774
775       if In_Extended_Main_Source_Unit (N) then
776          return False;
777
778       --  If loaded by rtsfind, then suppress message
779
780       elsif Sloc (N) <= No_Location then
781          return True;
782
783       --  Otherwise suppress message if internal file
784
785       else
786          return Is_Internal_File_Name (Unit_File_Name (Get_Source_Unit (N)));
787       end if;
788    end Suppress_Restriction_Message;
789
790    ---------------------
791    -- Tasking_Allowed --
792    ---------------------
793
794    function Tasking_Allowed return Boolean is
795    begin
796       return not Restrictions.Set (No_Tasking)
797         and then (not Restrictions.Set (Max_Tasks)
798                     or else Restrictions.Value (Max_Tasks) > 0);
799    end Tasking_Allowed;
800
801 end Restrict;