sem_ch4.adb (Try_Object_Operation): Reformat the code to expand in-line the code...
[platform/upstream/gcc.git] / gcc / ada / s-interr-vms.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                GNU ADA RUN-TIME LIBRARY (GNARL) COMPONENTS               --
4 --                                                                          --
5 --                     S Y S T E M . I N T E R R U P T S                    --
6 --                                                                          --
7 --                                  B o d y                                 --
8 --                                                                          --
9 --         Copyright (C) 1992-2004, Free Software Foundation, Inc.          --
10 --                                                                          --
11 -- GNARL 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 2,  or (at your option) any later ver- --
14 -- sion. GNARL 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 GNARL; see file COPYING.  If not, write --
19 -- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
20 -- MA 02111-1307, USA.                                                      --
21 --                                                                          --
22 -- As a special exception,  if other files  instantiate  generics from this --
23 -- unit, or you link  this unit with other files  to produce an executable, --
24 -- this  unit  does not  by itself cause  the resulting  executable  to  be --
25 -- covered  by the  GNU  General  Public  License.  This exception does not --
26 -- however invalidate  any other reasons why  the executable file  might be --
27 -- covered by the  GNU Public License.                                      --
28 --                                                                          --
29 -- GNARL was developed by the GNARL team at Florida State University.       --
30 -- Extensive contributions were provided by Ada Core Technologies, Inc.     --
31 --                                                                          --
32 ------------------------------------------------------------------------------
33
34 --  This is an OpenVMS/Alpha version of this package.
35
36 --  Invariants:
37
38 --  Once we associate a Server_Task with an interrupt, the task never
39 --  goes away, and we never remove the association.
40
41 --  There is no more than one interrupt per Server_Task and no more than
42 --  one Server_Task per interrupt.
43
44 --  Within this package, the lock L is used to protect the various status
45 --  tables. If there is a Server_Task associated with an interrupt, we use
46 --  the per-task lock of the Server_Task instead so that we protect the
47 --  status between Interrupt_Manager and Server_Task. Protection among
48 --  service requests are done using User Request to Interrupt_Manager
49 --  rendezvous.
50
51 with Ada.Task_Identification;
52 --  used for Task_Id type
53
54 with Ada.Exceptions;
55 --  used for Raise_Exception
56
57 with System.Task_Primitives;
58 --  used for RTS_Lock
59 --           Self
60
61 with System.Interrupt_Management;
62 --  used for Reserve
63 --           Interrupt_ID
64 --           Interrupt_Mask
65 --           Abort_Task_Interrupt
66
67 with System.Interrupt_Management.Operations;
68 --  used for Thread_Block_Interrupt
69 --           Thread_Unblock_Interrupt
70 --           Install_Default_Action
71 --           Install_Ignore_Action
72 --           Copy_Interrupt_Mask
73 --           Set_Interrupt_Mask
74 --           Empty_Interrupt_Mask
75 --           Fill_Interrupt_Mask
76 --           Add_To_Interrupt_Mask
77 --           Delete_From_Interrupt_Mask
78 --           Interrupt_Wait
79 --           Interrupt_Self_Process
80 --           Get_Interrupt_Mask
81 --           Set_Interrupt_Mask
82 --           IS_Member
83 --           Environment_Mask
84 pragma Elaborate_All (System.Interrupt_Management.Operations);
85
86 with System.Task_Primitives.Operations;
87 --  used for Write_Lock
88 --           Unlock
89 --           Abort
90 --           Wakeup_Task
91 --           Sleep
92 --           Initialize_Lock
93
94 with System.Task_Primitives.Interrupt_Operations;
95 --  used for Set_Interrupt_ID
96
97 with System.Storage_Elements;
98 --  used for To_Address
99 --           To_Integer
100 --           Integer_Address
101
102 with System.Tasking;
103 --  used for Task_Id
104 --           Task_Entry_Index
105 --           Null_Task
106 --           Self
107 --           Interrupt_Manager_ID
108
109 with System.Tasking.Utilities;
110 --  used for Make_Independent
111
112 with System.Tasking.Rendezvous;
113 --  used for Call_Simple
114 pragma Elaborate_All (System.Tasking.Rendezvous);
115
116 with System.Tasking.Initialization;
117 --  used for Defer_Abort
118 --           Undefer_Abort
119
120 with System.Parameters;
121 --  used for Single_Lock
122
123 with Unchecked_Conversion;
124
125 package body System.Interrupts is
126
127    use Tasking;
128    use System.Parameters;
129    use Ada.Exceptions;
130
131    package POP renames System.Task_Primitives.Operations;
132    package PIO renames System.Task_Primitives.Interrupt_Operations;
133    package IMNG renames System.Interrupt_Management;
134    package IMOP renames System.Interrupt_Management.Operations;
135
136    function To_System is new Unchecked_Conversion
137      (Ada.Task_Identification.Task_Id, Task_Id);
138
139    -----------------
140    -- Local Tasks --
141    -----------------
142
143    --  WARNING: System.Tasking.Stages performs calls to this task
144    --  with low-level constructs. Do not change this spec without synchro-
145    --  nizing it.
146
147    task Interrupt_Manager is
148       entry Detach_Interrupt_Entries (T : Task_Id);
149
150       entry Initialize (Mask : IMNG.Interrupt_Mask);
151
152       entry Attach_Handler
153         (New_Handler : Parameterless_Handler;
154          Interrupt   : Interrupt_ID;
155          Static      : Boolean;
156          Restoration : Boolean := False);
157
158       entry Exchange_Handler
159         (Old_Handler : out Parameterless_Handler;
160          New_Handler : Parameterless_Handler;
161          Interrupt   : Interrupt_ID;
162          Static      : Boolean);
163
164       entry Detach_Handler
165         (Interrupt   : Interrupt_ID;
166          Static      : Boolean);
167
168       entry Bind_Interrupt_To_Entry
169         (T         : Task_Id;
170          E         : Task_Entry_Index;
171          Interrupt : Interrupt_ID);
172
173       entry Block_Interrupt (Interrupt : Interrupt_ID);
174
175       entry Unblock_Interrupt (Interrupt : Interrupt_ID);
176
177       entry Ignore_Interrupt (Interrupt : Interrupt_ID);
178
179       entry Unignore_Interrupt (Interrupt : Interrupt_ID);
180
181       pragma Interrupt_Priority (System.Interrupt_Priority'Last);
182    end Interrupt_Manager;
183
184    task type Server_Task (Interrupt : Interrupt_ID) is
185       pragma Priority (System.Interrupt_Priority'Last);
186       --  Note: the above pragma Priority is strictly speaking improper
187       --  since it is outside the range of allowed priorities, but the
188       --  compiler treats system units specially and does not apply
189       --  this range checking rule to system units.
190
191    end Server_Task;
192
193    type Server_Task_Access is access Server_Task;
194
195    -------------------------------
196    -- Local Types and Variables --
197    -------------------------------
198
199    type Entry_Assoc is record
200       T : Task_Id;
201       E : Task_Entry_Index;
202    end record;
203
204    type Handler_Assoc is record
205       H      : Parameterless_Handler;
206       Static : Boolean;   --  Indicates static binding;
207    end record;
208
209    User_Handler : array (Interrupt_ID'Range) of Handler_Assoc :=
210                     (others => (null, Static => False));
211    pragma Volatile_Components (User_Handler);
212    --  Holds the protected procedure handler (if any) and its Static
213    --  information  for each interrupt. A handler is a Static one if
214    --  it is specified through the pragma Attach_Handler.
215    --  Attach_Handler. Otherwise, not static)
216
217    User_Entry : array (Interrupt_ID'Range) of Entry_Assoc :=
218                   (others => (T => Null_Task, E => Null_Task_Entry));
219    pragma Volatile_Components (User_Entry);
220    --  Holds the task and entry index (if any) for each interrupt
221
222    Blocked : constant array (Interrupt_ID'Range) of Boolean :=
223      (others => False);
224 --  ??? pragma Volatile_Components (Blocked);
225    --  True iff the corresponding interrupt is blocked in the process level
226
227    Ignored : array (Interrupt_ID'Range) of Boolean := (others => False);
228    pragma Volatile_Components (Ignored);
229    --  True iff the corresponding interrupt is blocked in the process level
230
231    Last_Unblocker : constant array (Interrupt_ID'Range) of Task_Id :=
232      (others => Null_Task);
233 --  ??? pragma Volatile_Components (Last_Unblocker);
234    --  Holds the ID of the last Task which Unblocked this Interrupt.
235    --  It contains Null_Task if no tasks have ever requested the
236    --  Unblocking operation or the Interrupt is currently Blocked.
237
238    Server_ID : array (Interrupt_ID'Range) of Task_Id :=
239                  (others => Null_Task);
240    pragma Atomic_Components (Server_ID);
241    --  Holds the Task_Id of the Server_Task for each interrupt.
242    --  Task_Id is needed to accomplish locking per Interrupt base. Also
243    --  is needed to decide whether to create a new Server_Task.
244
245    --  Type and Head, Tail of the list containing Registered Interrupt
246    --  Handlers. These definitions are used to register the handlers
247    --  specified by the pragma Interrupt_Handler.
248
249    type Registered_Handler;
250    type R_Link is access all Registered_Handler;
251
252    type Registered_Handler is record
253       H :    System.Address := System.Null_Address;
254       Next : R_Link := null;
255    end record;
256
257    Registered_Handler_Head : R_Link := null;
258    Registered_Handler_Tail : R_Link := null;
259
260    Access_Hold : Server_Task_Access;
261    --  variable used to allocate Server_Task using "new".
262
263    -----------------------
264    -- Local Subprograms --
265    -----------------------
266
267    function Is_Registered (Handler : Parameterless_Handler) return Boolean;
268    --  See if the Handler has been "pragma"ed using Interrupt_Handler.
269    --  Always consider a null handler as registered.
270
271    --------------------------------
272    -- Register_Interrupt_Handler --
273    --------------------------------
274
275    procedure Register_Interrupt_Handler (Handler_Addr : System.Address) is
276       New_Node_Ptr : R_Link;
277    begin
278       --  This routine registers the Handler as usable for Dynamic
279       --  Interrupt Handler. Routines attaching and detaching Handler
280       --  dynamically should first consult if the Handler is rgistered.
281       --  A Program Error should be raised if it is not registered.
282
283       --  The pragma Interrupt_Handler can only appear in the library
284       --  level PO definition and instantiation. Therefore, we do not need
285       --  to implement Unregistering operation. Neither we need to
286       --  protect the queue structure using a Lock.
287
288       pragma Assert (Handler_Addr /= System.Null_Address);
289
290       New_Node_Ptr := new Registered_Handler;
291       New_Node_Ptr.H := Handler_Addr;
292
293       if Registered_Handler_Head = null then
294          Registered_Handler_Head := New_Node_Ptr;
295          Registered_Handler_Tail := New_Node_Ptr;
296
297       else
298          Registered_Handler_Tail.Next := New_Node_Ptr;
299          Registered_Handler_Tail := New_Node_Ptr;
300       end if;
301    end Register_Interrupt_Handler;
302
303    -------------------
304    -- Is_Registered --
305    -------------------
306
307    function Is_Registered (Handler : Parameterless_Handler) return Boolean is
308       type Fat_Ptr is record
309          Object_Addr  : System.Address;
310          Handler_Addr : System.Address;
311       end record;
312
313       function To_Fat_Ptr is new Unchecked_Conversion
314         (Parameterless_Handler, Fat_Ptr);
315
316       Ptr : R_Link;
317       Fat : Fat_Ptr;
318
319    begin
320       if Handler = null then
321          return True;
322       end if;
323
324       Fat := To_Fat_Ptr (Handler);
325
326       Ptr := Registered_Handler_Head;
327
328       while Ptr /= null loop
329          if Ptr.H = Fat.Handler_Addr then
330             return True;
331          end if;
332
333          Ptr := Ptr.Next;
334       end loop;
335
336       return False;
337
338    end Is_Registered;
339
340    -----------------
341    -- Is_Reserved --
342    -----------------
343
344    function Is_Reserved (Interrupt : Interrupt_ID) return Boolean is
345    begin
346       return IMNG.Reserve (IMNG.Interrupt_ID (Interrupt));
347    end Is_Reserved;
348
349    -----------------------
350    -- Is_Entry_Attached --
351    -----------------------
352
353    function Is_Entry_Attached (Interrupt : Interrupt_ID) return Boolean is
354    begin
355       if Is_Reserved (Interrupt) then
356          Raise_Exception (Program_Error'Identity, "Interrupt" &
357            Interrupt_ID'Image (Interrupt) & " is reserved");
358       end if;
359
360       return User_Entry (Interrupt).T /= Null_Task;
361    end Is_Entry_Attached;
362
363    -------------------------
364    -- Is_Handler_Attached --
365    -------------------------
366
367    function Is_Handler_Attached (Interrupt : Interrupt_ID) return Boolean is
368    begin
369       if Is_Reserved (Interrupt) then
370          Raise_Exception (Program_Error'Identity, "Interrupt" &
371            Interrupt_ID'Image (Interrupt) & " is reserved");
372       end if;
373
374       return User_Handler (Interrupt).H /= null;
375    end Is_Handler_Attached;
376
377    ----------------
378    -- Is_Blocked --
379    ----------------
380
381    function Is_Blocked (Interrupt : Interrupt_ID) return Boolean is
382    begin
383       if Is_Reserved (Interrupt) then
384          Raise_Exception (Program_Error'Identity, "Interrupt" &
385            Interrupt_ID'Image (Interrupt) & " is reserved");
386       end if;
387
388       return Blocked (Interrupt);
389    end Is_Blocked;
390
391    ----------------
392    -- Is_Ignored --
393    ----------------
394
395    function Is_Ignored (Interrupt : Interrupt_ID) return Boolean is
396    begin
397       if Is_Reserved (Interrupt) then
398          Raise_Exception (Program_Error'Identity, "Interrupt" &
399            Interrupt_ID'Image (Interrupt) & " is reserved");
400       end if;
401
402       return Ignored (Interrupt);
403    end Is_Ignored;
404
405    ---------------------
406    -- Current_Handler --
407    ---------------------
408
409    function Current_Handler
410      (Interrupt : Interrupt_ID) return Parameterless_Handler
411    is
412    begin
413       if Is_Reserved (Interrupt) then
414          Raise_Exception (Program_Error'Identity, "Interrupt" &
415            Interrupt_ID'Image (Interrupt) & " is reserved");
416       end if;
417
418       --  ??? Since Parameterless_Handler is not Atomic, the
419       --  current implementation is wrong. We need a new service in
420       --  Interrupt_Manager to ensure atomicity.
421
422       return User_Handler (Interrupt).H;
423    end Current_Handler;
424
425    --------------------
426    -- Attach_Handler --
427    --------------------
428
429    --  Calling this procedure with New_Handler = null and Static = True
430    --  means we want to detach the current handler regardless of the
431    --  previous handler's binding status (ie. do not care if it is a
432    --  dynamic or static handler).
433
434    --  This option is needed so that during the finalization of a PO, we
435    --  can detach handlers attached through pragma Attach_Handler.
436
437    procedure Attach_Handler
438      (New_Handler : Parameterless_Handler;
439       Interrupt   : Interrupt_ID;
440       Static      : Boolean := False) is
441    begin
442       if Is_Reserved (Interrupt) then
443          Raise_Exception (Program_Error'Identity, "Interrupt" &
444            Interrupt_ID'Image (Interrupt) & " is reserved");
445       end if;
446
447       Interrupt_Manager.Attach_Handler (New_Handler, Interrupt, Static);
448
449    end Attach_Handler;
450
451    ----------------------
452    -- Exchange_Handler --
453    ----------------------
454
455    --  Calling this procedure with New_Handler = null and Static = True
456    --  means we want to detach the current handler regardless of the
457    --  previous handler's binding status (ie. do not care if it is a
458    --  dynamic or static handler).
459
460    --  This option is needed so that during the finalization of a PO, we
461    --  can detach handlers attached through pragma Attach_Handler.
462
463    procedure Exchange_Handler
464      (Old_Handler : out Parameterless_Handler;
465       New_Handler : Parameterless_Handler;
466       Interrupt   : Interrupt_ID;
467       Static      : Boolean := False) is
468    begin
469       if Is_Reserved (Interrupt) then
470          Raise_Exception (Program_Error'Identity, "Interrupt" &
471            Interrupt_ID'Image (Interrupt) & " is reserved");
472       end if;
473
474       Interrupt_Manager.Exchange_Handler
475         (Old_Handler, New_Handler, Interrupt, Static);
476
477    end Exchange_Handler;
478
479    --------------------
480    -- Detach_Handler --
481    --------------------
482
483    --  Calling this procedure with Static = True means we want to Detach the
484    --  current handler regardless of the previous handler's binding status
485    --  (i.e. do not care if it is a dynamic or static handler).
486
487    --  This option is needed so that during the finalization of a PO, we can
488    --  detach handlers attached through pragma Attach_Handler.
489
490    procedure Detach_Handler
491      (Interrupt : Interrupt_ID;
492       Static    : Boolean := False)
493    is
494    begin
495       if Is_Reserved (Interrupt) then
496          Raise_Exception (Program_Error'Identity, "Interrupt" &
497            Interrupt_ID'Image (Interrupt) & " is reserved");
498       end if;
499
500       Interrupt_Manager.Detach_Handler (Interrupt, Static);
501    end Detach_Handler;
502
503    ---------------
504    -- Reference --
505    ---------------
506
507    function Reference (Interrupt : Interrupt_ID) return System.Address is
508    begin
509       if Is_Reserved (Interrupt) then
510          Raise_Exception (Program_Error'Identity, "Interrupt" &
511            Interrupt_ID'Image (Interrupt) & " is reserved");
512       end if;
513
514       return Storage_Elements.To_Address
515         (Storage_Elements.Integer_Address (Interrupt));
516    end Reference;
517
518    -----------------------------
519    -- Bind_Interrupt_To_Entry --
520    -----------------------------
521
522    --  This procedure raises a Program_Error if it tries to
523    --  bind an interrupt to which an Entry or a Procedure is
524    --  already bound.
525
526    procedure Bind_Interrupt_To_Entry
527      (T       : Task_Id;
528       E       : Task_Entry_Index;
529       Int_Ref : System.Address)
530    is
531       Interrupt : constant Interrupt_ID :=
532         Interrupt_ID (Storage_Elements.To_Integer (Int_Ref));
533
534    begin
535       if Is_Reserved (Interrupt) then
536          Raise_Exception (Program_Error'Identity, "Interrupt" &
537            Interrupt_ID'Image (Interrupt) & " is reserved");
538       end if;
539
540       Interrupt_Manager.Bind_Interrupt_To_Entry (T, E, Interrupt);
541
542    end Bind_Interrupt_To_Entry;
543
544    ------------------------------
545    -- Detach_Interrupt_Entries --
546    ------------------------------
547
548    procedure Detach_Interrupt_Entries (T : Task_Id) is
549    begin
550       Interrupt_Manager.Detach_Interrupt_Entries (T);
551    end Detach_Interrupt_Entries;
552
553    ---------------------
554    -- Block_Interrupt --
555    ---------------------
556
557    procedure Block_Interrupt (Interrupt : Interrupt_ID) is
558    begin
559       if Is_Reserved (Interrupt) then
560          Raise_Exception (Program_Error'Identity, "Interrupt" &
561            Interrupt_ID'Image (Interrupt) & " is reserved");
562       end if;
563
564       Interrupt_Manager.Block_Interrupt (Interrupt);
565    end Block_Interrupt;
566
567    -----------------------
568    -- Unblock_Interrupt --
569    -----------------------
570
571    procedure Unblock_Interrupt (Interrupt : Interrupt_ID) is
572    begin
573       if Is_Reserved (Interrupt) then
574          Raise_Exception (Program_Error'Identity, "Interrupt" &
575            Interrupt_ID'Image (Interrupt) & " is reserved");
576       end if;
577
578       Interrupt_Manager.Unblock_Interrupt (Interrupt);
579    end Unblock_Interrupt;
580
581    ------------------
582    -- Unblocked_By --
583    ------------------
584
585    function Unblocked_By
586      (Interrupt : Interrupt_ID) return System.Tasking.Task_Id is
587    begin
588       if Is_Reserved (Interrupt) then
589          Raise_Exception (Program_Error'Identity, "Interrupt" &
590            Interrupt_ID'Image (Interrupt) & " is reserved");
591       end if;
592
593       return Last_Unblocker (Interrupt);
594    end Unblocked_By;
595
596    ----------------------
597    -- Ignore_Interrupt --
598    ----------------------
599
600    procedure Ignore_Interrupt (Interrupt : Interrupt_ID) is
601    begin
602       if Is_Reserved (Interrupt) then
603          Raise_Exception (Program_Error'Identity, "Interrupt" &
604            Interrupt_ID'Image (Interrupt) & " is reserved");
605       end if;
606
607       Interrupt_Manager.Ignore_Interrupt (Interrupt);
608    end Ignore_Interrupt;
609
610    ------------------------
611    -- Unignore_Interrupt --
612    ------------------------
613
614    procedure Unignore_Interrupt (Interrupt : Interrupt_ID) is
615    begin
616       if Is_Reserved (Interrupt) then
617          Raise_Exception (Program_Error'Identity, "Interrupt" &
618            Interrupt_ID'Image (Interrupt) & " is reserved");
619       end if;
620
621       Interrupt_Manager.Unignore_Interrupt (Interrupt);
622    end Unignore_Interrupt;
623
624    -----------------------
625    -- Interrupt_Manager --
626    -----------------------
627
628    task body Interrupt_Manager is
629
630       --------------------
631       -- Local Routines --
632       --------------------
633
634       procedure Unprotected_Exchange_Handler
635         (Old_Handler : out Parameterless_Handler;
636          New_Handler : Parameterless_Handler;
637          Interrupt   : Interrupt_ID;
638          Static      : Boolean;
639          Restoration : Boolean := False);
640
641       procedure Unprotected_Detach_Handler
642         (Interrupt : Interrupt_ID;
643          Static    : Boolean);
644
645       ----------------------------------
646       -- Unprotected_Exchange_Handler --
647       ----------------------------------
648
649       procedure Unprotected_Exchange_Handler
650         (Old_Handler : out Parameterless_Handler;
651          New_Handler : Parameterless_Handler;
652          Interrupt   : Interrupt_ID;
653          Static      : Boolean;
654          Restoration : Boolean := False)
655       is
656       begin
657          if User_Entry (Interrupt).T /= Null_Task then
658             --  In case we have an Interrupt Entry already installed.
659             --  raise a program error. (propagate it to the caller).
660
661             Raise_Exception (Program_Error'Identity,
662               "An interrupt is already installed");
663          end if;
664
665          --  Note : A null handler with Static = True will
666          --  pass the following check. That is the case when we want to
667          --  Detach a handler regardless of the Static status
668          --  of the current_Handler.
669          --  We don't check anything if Restoration is True, since we
670          --  may be detaching a static handler to restore a dynamic one.
671
672          if not Restoration and then not Static
673             --  Tries to overwrite a static Interrupt Handler with a
674             --  dynamic Handler
675
676            and then (User_Handler (Interrupt).Static
677
678                         --  The new handler is not specified as an
679                         --  Interrupt Handler by a pragma.
680
681                         or else not Is_Registered (New_Handler))
682          then
683             Raise_Exception (Program_Error'Identity,
684               "Trying to overwrite a static Interrupt Handler with a " &
685               "dynamic Handler");
686          end if;
687
688          --  The interrupt should no longer be ingnored if
689          --  it was ever ignored.
690
691          Ignored (Interrupt) := False;
692
693          --  Save the old handler
694
695          Old_Handler := User_Handler (Interrupt).H;
696
697          --  The new handler
698
699          User_Handler (Interrupt).H := New_Handler;
700
701          if New_Handler = null then
702
703             --  The null handler means we are detaching the handler.
704
705             User_Handler (Interrupt).Static := False;
706
707          else
708             User_Handler (Interrupt).Static := Static;
709          end if;
710
711          --  Invoke a corresponding Server_Task if not yet created.
712          --  Place Task_Id info in Server_ID array.
713
714          if Server_ID (Interrupt) = Null_Task then
715             Access_Hold := new Server_Task (Interrupt);
716             Server_ID (Interrupt) := To_System (Access_Hold.all'Identity);
717          else
718             POP.Wakeup (Server_ID (Interrupt), Interrupt_Server_Idle_Sleep);
719          end if;
720
721       end Unprotected_Exchange_Handler;
722
723       --------------------------------
724       -- Unprotected_Detach_Handler --
725       --------------------------------
726
727       procedure Unprotected_Detach_Handler
728         (Interrupt   : Interrupt_ID;
729          Static      : Boolean)
730       is
731       begin
732          if User_Entry (Interrupt).T /= Null_Task then
733             --  In case we have an Interrupt Entry installed.
734             --  raise a program error. (propagate it to the caller).
735
736             Raise_Exception (Program_Error'Identity,
737               "An interrupt entry is already installed");
738          end if;
739
740          --  Note : Static = True will pass the following check. That is the
741          --  case when we want to detach a handler regardless of the static
742          --  status of the current_Handler.
743
744          if not Static and then User_Handler (Interrupt).Static then
745             --  Tries to detach a static Interrupt Handler.
746             --  raise a program error.
747
748             Raise_Exception (Program_Error'Identity,
749               "Trying to detach a static Interrupt Handler");
750          end if;
751
752          --  The interrupt should no longer be ignored if
753          --  it was ever ignored.
754
755          Ignored (Interrupt) := False;
756
757          --  The new handler
758
759          User_Handler (Interrupt).H := null;
760          User_Handler (Interrupt).Static := False;
761          IMOP.Interrupt_Self_Process (IMNG.Interrupt_ID (Interrupt));
762
763       end Unprotected_Detach_Handler;
764
765    --  Start of processing for Interrupt_Manager
766
767    begin
768       --  By making this task independent of master, when the process
769       --  goes away, the Interrupt_Manager will terminate gracefully.
770
771       System.Tasking.Utilities.Make_Independent;
772
773       --  Environmen task gets its own interrupt mask, saves it,
774       --  and then masks all interrupts except the Keep_Unmasked set.
775
776       --  During rendezvous, the Interrupt_Manager receives the old
777       --  interrupt mask of the environment task, and sets its own
778       --  interrupt mask to that value.
779
780       --  The environment task will call the entry of Interrupt_Manager some
781       --  during elaboration of the body of this package.
782
783       accept Initialize (Mask : IMNG.Interrupt_Mask) do
784          pragma Warnings (Off, Mask);
785          null;
786       end Initialize;
787
788       --  Note: All tasks in RTS will have all the Reserve Interrupts
789       --  being masked (except the Interrupt_Manager) and Keep_Unmasked
790       --  unmasked when created.
791
792       --  Abort_Task_Interrupt is one of the Interrupt unmasked
793       --  in all tasks. We mask the Interrupt in this particular task
794       --  so that "sigwait" is possible to catch an explicitely sent
795       --  Abort_Task_Interrupt from the Server_Tasks.
796
797       --  This sigwaiting is needed so that we make sure a Server_Task is
798       --  out of its own sigwait state. This extra synchronization is
799       --  necessary to prevent following senarios.
800
801       --   1) Interrupt_Manager sends an Abort_Task_Interrupt to the
802       --      Server_Task then changes its own interrupt mask (OS level).
803       --      If an interrupt (corresponding to the Server_Task) arrives
804       --      in the nean time we have the Interrupt_Manager umnasked and
805       --      the Server_Task waiting on sigwait.
806
807       --   2) For unbinding handler, we install a default action in the
808       --      Interrupt_Manager. POSIX.1c states that the result of using
809       --      "sigwait" and "sigaction" simaltaneously on the same interrupt
810       --      is undefined. Therefore, we need to be informed from the
811       --      Server_Task of the fact that the Server_Task is out of its
812       --      sigwait stage.
813
814       loop
815          --  A block is needed to absorb Program_Error exception
816
817          declare
818             Old_Handler : Parameterless_Handler;
819          begin
820             select
821
822             accept Attach_Handler
823                (New_Handler : Parameterless_Handler;
824                 Interrupt   : Interrupt_ID;
825                 Static      : Boolean;
826                 Restoration : Boolean := False)
827             do
828                Unprotected_Exchange_Handler
829                  (Old_Handler, New_Handler, Interrupt, Static, Restoration);
830             end Attach_Handler;
831
832             or accept Exchange_Handler
833                (Old_Handler : out Parameterless_Handler;
834                 New_Handler : Parameterless_Handler;
835                 Interrupt   : Interrupt_ID;
836                 Static      : Boolean)
837             do
838                Unprotected_Exchange_Handler
839                  (Old_Handler, New_Handler, Interrupt, Static);
840             end Exchange_Handler;
841
842             or accept Detach_Handler
843                (Interrupt   : Interrupt_ID;
844                 Static      : Boolean)
845             do
846                Unprotected_Detach_Handler (Interrupt, Static);
847             end Detach_Handler;
848
849             or accept Bind_Interrupt_To_Entry
850               (T       : Task_Id;
851                E       : Task_Entry_Index;
852                Interrupt : Interrupt_ID)
853             do
854                --  if there is a binding already (either a procedure or an
855                --  entry), raise Program_Error (propagate it to the caller).
856
857                if User_Handler (Interrupt).H /= null
858                  or else User_Entry (Interrupt).T /= Null_Task
859                then
860                   Raise_Exception (Program_Error'Identity,
861                     "A binding for this interrupt is already present");
862                end if;
863
864                --  The interrupt should no longer be ingnored if
865                --  it was ever ignored.
866
867                Ignored (Interrupt) := False;
868                User_Entry (Interrupt) := Entry_Assoc'(T => T, E => E);
869
870                --  Indicate the attachment of Interrupt Entry in ATCB.
871                --  This is need so that when an Interrupt Entry task
872                --  terminates the binding can be cleaned.
873                --  The call to unbinding must be
874                --  make by the task before it terminates.
875
876                T.Interrupt_Entry := True;
877
878                --  Invoke a corresponding Server_Task if not yet created.
879                --  Place Task_Id info in Server_ID array.
880
881                if Server_ID (Interrupt) = Null_Task then
882
883                   Access_Hold := new Server_Task (Interrupt);
884                   Server_ID (Interrupt) :=
885                     To_System (Access_Hold.all'Identity);
886                else
887                   POP.Wakeup (Server_ID (Interrupt),
888                               Interrupt_Server_Idle_Sleep);
889                end if;
890             end Bind_Interrupt_To_Entry;
891
892             or accept Detach_Interrupt_Entries (T : Task_Id)
893             do
894                for J in Interrupt_ID'Range loop
895                   if not Is_Reserved (J) then
896                      if User_Entry (J).T = T then
897
898                         --  The interrupt should no longer be ignored if
899                         --  it was ever ignored.
900
901                         Ignored (J) := False;
902                         User_Entry (J) :=
903                           Entry_Assoc'(T => Null_Task, E => Null_Task_Entry);
904                         IMOP.Interrupt_Self_Process (IMNG.Interrupt_ID (J));
905                      end if;
906                   end if;
907                end loop;
908
909                --  Indicate in ATCB that no Interrupt Entries are attached.
910
911                T.Interrupt_Entry := False;
912             end Detach_Interrupt_Entries;
913
914             or accept Block_Interrupt (Interrupt : Interrupt_ID) do
915                pragma Warnings (Off, Interrupt);
916                raise Program_Error;
917             end Block_Interrupt;
918
919             or accept Unblock_Interrupt (Interrupt : Interrupt_ID) do
920                pragma Warnings (Off, Interrupt);
921                raise Program_Error;
922             end Unblock_Interrupt;
923
924             or accept Ignore_Interrupt (Interrupt : Interrupt_ID) do
925                pragma Warnings (Off, Interrupt);
926                raise Program_Error;
927             end Ignore_Interrupt;
928
929             or accept Unignore_Interrupt (Interrupt : Interrupt_ID) do
930                pragma Warnings (Off, Interrupt);
931                raise Program_Error;
932             end Unignore_Interrupt;
933
934             end select;
935
936          exception
937             --  If there is a program error we just want to propagate it
938             --  to the caller and do not want to stop this task.
939
940             when Program_Error =>
941                null;
942
943             when others =>
944                pragma Assert (False);
945                null;
946          end;
947       end loop;
948    end Interrupt_Manager;
949
950    -----------------
951    -- Server_Task --
952    -----------------
953
954    task body Server_Task is
955       Self_ID         : constant Task_Id := Self;
956       Tmp_Handler     : Parameterless_Handler;
957       Tmp_ID          : Task_Id;
958       Tmp_Entry_Index : Task_Entry_Index;
959       Intwait_Mask    : aliased IMNG.Interrupt_Mask;
960
961    begin
962       --  By making this task independent of master, when the process
963       --  goes away, the Server_Task will terminate gracefully.
964
965       System.Tasking.Utilities.Make_Independent;
966
967       --  Install default action in system level.
968
969       IMOP.Install_Default_Action (IMNG.Interrupt_ID (Interrupt));
970
971       --  Set up the mask (also clears the event flag)
972
973       IMOP.Empty_Interrupt_Mask (Intwait_Mask'Access);
974       IMOP.Add_To_Interrupt_Mask
975         (Intwait_Mask'Access, IMNG.Interrupt_ID (Interrupt));
976
977       --  Remember the Interrupt_ID for Abort_Task.
978
979       PIO.Set_Interrupt_ID (IMNG.Interrupt_ID (Interrupt), Self_ID);
980
981       --  Note: All tasks in RTS will have all the Reserve Interrupts
982       --  being masked (except the Interrupt_Manager) and Keep_Unmasked
983       --  unmasked when created.
984
985       loop
986          System.Tasking.Initialization.Defer_Abort (Self_ID);
987
988          --  A Handler or an Entry is installed. At this point all tasks
989          --  mask for the Interrupt is masked. Catch the Interrupt using
990          --  sigwait.
991
992          --  This task may wake up from sigwait by receiving an interrupt
993          --  (Abort_Task_Interrupt) from the Interrupt_Manager for unbinding
994          --  a Procedure Handler or an Entry. Or it could be a wake up
995          --  from status change (Unblocked -> Blocked). If that is not
996          --  the case, we should exceute the attached Procedure or Entry.
997
998          if Single_Lock then
999             POP.Lock_RTS;
1000          end if;
1001
1002          POP.Write_Lock (Self_ID);
1003
1004          if User_Handler (Interrupt).H = null
1005            and then User_Entry (Interrupt).T = Null_Task
1006          then
1007             --  No Interrupt binding. If there is an interrupt,
1008             --  Interrupt_Manager will take default action.
1009
1010             Self_ID.Common.State := Interrupt_Server_Idle_Sleep;
1011             POP.Sleep (Self_ID, Interrupt_Server_Idle_Sleep);
1012             Self_ID.Common.State := Runnable;
1013
1014          else
1015             Self_ID.Common.State := Interrupt_Server_Blocked_On_Event_Flag;
1016             Self_ID.Common.State := Runnable;
1017
1018             if not (Self_ID.Deferral_Level = 0
1019                     and then Self_ID.Pending_ATC_Level
1020                              < Self_ID.ATC_Nesting_Level)
1021             then
1022                if User_Handler (Interrupt).H /= null then
1023                   Tmp_Handler := User_Handler (Interrupt).H;
1024
1025                   --  RTS calls should not be made with self being locked.
1026
1027                   POP.Unlock (Self_ID);
1028
1029                   if Single_Lock then
1030                      POP.Unlock_RTS;
1031                   end if;
1032
1033                   Tmp_Handler.all;
1034
1035                   if Single_Lock then
1036                      POP.Lock_RTS;
1037                   end if;
1038
1039                   POP.Write_Lock (Self_ID);
1040
1041                elsif User_Entry (Interrupt).T /= Null_Task then
1042                   Tmp_ID := User_Entry (Interrupt).T;
1043                   Tmp_Entry_Index := User_Entry (Interrupt).E;
1044
1045                   --  RTS calls should not be made with self being locked.
1046
1047                   POP.Unlock (Self_ID);
1048
1049                   if Single_Lock then
1050                      POP.Unlock_RTS;
1051                   end if;
1052
1053                   System.Tasking.Rendezvous.Call_Simple
1054                     (Tmp_ID, Tmp_Entry_Index, System.Null_Address);
1055
1056                   if Single_Lock then
1057                      POP.Lock_RTS;
1058                   end if;
1059
1060                   POP.Write_Lock (Self_ID);
1061                end if;
1062             end if;
1063          end if;
1064
1065          POP.Unlock (Self_ID);
1066
1067          if Single_Lock then
1068             POP.Unlock_RTS;
1069          end if;
1070
1071          System.Tasking.Initialization.Undefer_Abort (Self_ID);
1072
1073          --  Undefer abort here to allow a window for this task
1074          --  to be aborted  at the time of system shutdown.
1075       end loop;
1076    end Server_Task;
1077
1078    -------------------------------------
1079    -- Has_Interrupt_Or_Attach_Handler --
1080    -------------------------------------
1081
1082    function Has_Interrupt_Or_Attach_Handler
1083      (Object : access Dynamic_Interrupt_Protection) return Boolean
1084    is
1085       pragma Warnings (Off, Object);
1086
1087    begin
1088       return True;
1089    end Has_Interrupt_Or_Attach_Handler;
1090
1091    --------------
1092    -- Finalize --
1093    --------------
1094
1095    procedure Finalize (Object : in out Static_Interrupt_Protection) is
1096    begin
1097       --  ??? loop to be executed only when we're not doing library level
1098       --  finalization, since in this case all interrupt tasks are gone.
1099
1100       if not Interrupt_Manager'Terminated then
1101          for N in reverse Object.Previous_Handlers'Range loop
1102             Interrupt_Manager.Attach_Handler
1103               (New_Handler => Object.Previous_Handlers (N).Handler,
1104                Interrupt   => Object.Previous_Handlers (N).Interrupt,
1105                Static      => Object.Previous_Handlers (N).Static,
1106                Restoration => True);
1107          end loop;
1108       end if;
1109
1110       Tasking.Protected_Objects.Entries.Finalize
1111         (Tasking.Protected_Objects.Entries.Protection_Entries (Object));
1112    end Finalize;
1113
1114    -------------------------------------
1115    -- Has_Interrupt_Or_Attach_Handler --
1116    -------------------------------------
1117
1118    function Has_Interrupt_Or_Attach_Handler
1119      (Object : access Static_Interrupt_Protection) return Boolean
1120    is
1121       pragma Warnings (Off, Object);
1122    begin
1123       return True;
1124    end Has_Interrupt_Or_Attach_Handler;
1125
1126    ----------------------
1127    -- Install_Handlers --
1128    ----------------------
1129
1130    procedure Install_Handlers
1131      (Object       : access Static_Interrupt_Protection;
1132       New_Handlers : New_Handler_Array)
1133    is
1134    begin
1135       for N in New_Handlers'Range loop
1136
1137          --  We need a lock around this ???
1138
1139          Object.Previous_Handlers (N).Interrupt := New_Handlers (N).Interrupt;
1140          Object.Previous_Handlers (N).Static    := User_Handler
1141            (New_Handlers (N).Interrupt).Static;
1142
1143          --  We call Exchange_Handler and not directly Interrupt_Manager.
1144          --  Exchange_Handler so we get the Is_Reserved check.
1145
1146          Exchange_Handler
1147            (Old_Handler => Object.Previous_Handlers (N).Handler,
1148             New_Handler => New_Handlers (N).Handler,
1149             Interrupt   => New_Handlers (N).Interrupt,
1150             Static      => True);
1151       end loop;
1152    end Install_Handlers;
1153
1154 --  Elaboration code for package System.Interrupts
1155 begin
1156
1157    --  Get Interrupt_Manager's ID so that Abort_Interrupt can be sent.
1158
1159    Interrupt_Manager_ID := To_System (Interrupt_Manager'Identity);
1160
1161    --  During the elaboration of this package body we want RTS to
1162    --  inherit the interrupt mask from the Environment Task.
1163
1164    --  The Environment Task should have gotten its mask from
1165    --  the enclosing process during the RTS start up. (See
1166    --  in s-inmaop.adb). Pass the Interrupt_Mask of the Environment
1167    --  task to the Interrupt_Manager.
1168
1169    --  Note : At this point we know that all tasks (including
1170    --  RTS internal servers) are masked for non-reserved signals
1171    --  (see s-taprop.adb). Only the Interrupt_Manager will have
1172    --  masks set up differently inheriting the original Environment
1173    --  Task's mask.
1174
1175    Interrupt_Manager.Initialize (IMOP.Environment_Mask);
1176 end System.Interrupts;