OSDN Git Service

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