OSDN Git Service

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