hppa: Fix LO_SUM DLTIND14R address support in PRINT_OPERAND_ADDRESS
[official-gcc.git] / gcc / ada / libgnarl / s-interr.adb
blob9962fbab1cd878e6e309e5f66a56cf3d4bd989db
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-2024, 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 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. --
17 -- --
18 -- As a special exception under Section 7 of GPL version 3, you are granted --
19 -- additional permissions described in the GCC Runtime Library Exception, --
20 -- version 3.1, as published by the Free Software Foundation. --
21 -- --
22 -- You should have received a copy of the GNU General Public License and --
23 -- a copy of the GCC Runtime Library Exception along with this program; --
24 -- see the files COPYING3 and COPYING.RUNTIME respectively. If not, see --
25 -- <http://www.gnu.org/licenses/>. --
26 -- --
27 -- GNARL was developed by the GNARL team at Florida State University. --
28 -- Extensive contributions were provided by Ada Core Technologies, Inc. --
29 -- --
30 ------------------------------------------------------------------------------
32 -- Invariants:
34 -- All user-handleable interrupts are masked at all times in all tasks/threads
35 -- except possibly for the Interrupt_Manager task.
37 -- When a user task wants to achieve masking/unmasking an interrupt, it must
38 -- call Block_Interrupt/Unblock_Interrupt, which will have the effect of
39 -- unmasking/masking the interrupt in the Interrupt_Manager task.
41 -- Note : Direct calls to sigaction, sigprocmask, pthread_sigsetmask or any
42 -- other low-level interface that changes the interrupt action or
43 -- interrupt mask needs a careful thought.
45 -- One may achieve the effect of system calls first masking RTS blocked
46 -- (by calling Block_Interrupt) for the interrupt under consideration.
47 -- This will make all the tasks in RTS blocked for the Interrupt.
49 -- Once we associate a Server_Task with an interrupt, the task never goes
50 -- away, and we never remove the association.
52 -- There is no more than one interrupt per Server_Task and no more than one
53 -- Server_Task per interrupt.
55 with Ada.Exceptions;
56 with Ada.Task_Identification;
57 with Ada.Unchecked_Conversion;
59 with System.Interrupt_Management;
60 with System.Interrupt_Management.Operations;
61 with System.IO;
62 with System.Parameters;
63 with System.Task_Primitives;
64 with System.Task_Primitives.Operations;
65 with System.Task_Primitives.Interrupt_Operations;
66 with System.Storage_Elements;
67 with System.Tasking.Initialization;
68 with System.Tasking.Utilities;
69 with System.Tasking.Rendezvous;
71 pragma Elaborate_All (System.Interrupt_Management.Operations);
72 pragma Elaborate_All (System.Tasking.Rendezvous);
74 package body System.Interrupts is
76 use Parameters;
77 use Tasking;
79 package POP renames System.Task_Primitives.Operations;
80 package PIO renames System.Task_Primitives.Interrupt_Operations;
81 package IMNG renames System.Interrupt_Management;
82 package IMOP renames System.Interrupt_Management.Operations;
84 function To_System is new Ada.Unchecked_Conversion
85 (Ada.Task_Identification.Task_Id, Task_Id);
87 -----------------
88 -- Local Tasks --
89 -----------------
91 -- WARNING: System.Tasking.Stages performs calls to this task with
92 -- low-level constructs. Do not change this spec without synchronizing it.
94 task Interrupt_Manager is
95 entry Detach_Interrupt_Entries (T : Task_Id);
97 entry Initialize (Mask : IMNG.Interrupt_Mask);
99 entry Attach_Handler
100 (New_Handler : Parameterless_Handler;
101 Interrupt : Interrupt_ID;
102 Static : Boolean;
103 Restoration : Boolean := False);
105 entry Exchange_Handler
106 (Old_Handler : out Parameterless_Handler;
107 New_Handler : Parameterless_Handler;
108 Interrupt : Interrupt_ID;
109 Static : Boolean);
111 entry Detach_Handler
112 (Interrupt : Interrupt_ID;
113 Static : Boolean);
115 entry Bind_Interrupt_To_Entry
116 (T : Task_Id;
117 E : Task_Entry_Index;
118 Interrupt : Interrupt_ID);
120 entry Block_Interrupt (Interrupt : Interrupt_ID);
122 entry Unblock_Interrupt (Interrupt : Interrupt_ID);
124 entry Ignore_Interrupt (Interrupt : Interrupt_ID);
126 entry Unignore_Interrupt (Interrupt : Interrupt_ID);
128 pragma Interrupt_Priority (System.Interrupt_Priority'Last);
129 end Interrupt_Manager;
131 task type Server_Task (Interrupt : Interrupt_ID) is
132 pragma Priority (System.Interrupt_Priority'Last);
133 -- Note: the above pragma Priority is strictly speaking improper since
134 -- it is outside the range of allowed priorities, but the compiler
135 -- treats system units specially and does not apply this range checking
136 -- rule to system units.
138 end Server_Task;
140 type Server_Task_Access is access Server_Task;
142 -------------------------------
143 -- Local Types and Variables --
144 -------------------------------
146 type Entry_Assoc is record
147 T : Task_Id;
148 E : Task_Entry_Index;
149 end record;
151 type Handler_Assoc is record
152 H : Parameterless_Handler;
153 Static : Boolean; -- Indicates static binding;
154 end record;
156 User_Handler : array (Interrupt_ID'Range) of Handler_Assoc :=
157 [others => (null, Static => False)];
158 pragma Volatile_Components (User_Handler);
159 -- Holds the protected procedure handler (if any) and its Static
160 -- information for each interrupt. A handler is a Static one if it is
161 -- specified through the pragma Attach_Handler. Attach_Handler. Otherwise,
162 -- not static)
164 User_Entry : array (Interrupt_ID'Range) of Entry_Assoc :=
165 [others => (T => Null_Task, E => Null_Task_Entry)];
166 pragma Volatile_Components (User_Entry);
167 -- Holds the task and entry index (if any) for each interrupt
169 Blocked : array (Interrupt_ID'Range) of Boolean := [others => False];
170 pragma Atomic_Components (Blocked);
171 -- True iff the corresponding interrupt is blocked in the process level
173 Ignored : array (Interrupt_ID'Range) of Boolean := [others => False];
174 pragma Atomic_Components (Ignored);
175 -- True iff the corresponding interrupt is blocked in the process level
177 Last_Unblocker : array (Interrupt_ID'Range) of Task_Id :=
178 [others => Null_Task];
179 pragma Atomic_Components (Last_Unblocker);
180 -- Holds the ID of the last Task which Unblocked this Interrupt. It
181 -- contains Null_Task if no tasks have ever requested the Unblocking
182 -- operation or the Interrupt is currently Blocked.
184 Server_ID : array (Interrupt_ID'Range) of Task_Id := [others => Null_Task];
185 pragma Atomic_Components (Server_ID);
186 -- Holds the Task_Id of the Server_Task for each interrupt. Task_Id is
187 -- needed to accomplish locking per Interrupt base. Also is needed to
188 -- decide whether to create a new Server_Task.
190 -- Type and the list containing Registered Interrupt Handlers. These
191 -- definitions are used to register the handlers specified by the pragma
192 -- Interrupt_Handler.
194 --------------------------
195 -- Handler Registration --
196 --------------------------
198 type Registered_Handler;
199 type R_Link is access all Registered_Handler;
201 type Registered_Handler is record
202 H : System.Address;
203 Next : R_Link;
204 end record;
206 Registered_Handlers : R_Link := null;
208 Access_Hold : Server_Task_Access;
209 -- Variable used to allocate Server_Task using "new"
211 -----------------------
212 -- Local Subprograms --
213 -----------------------
215 function Is_Registered (Handler : Parameterless_Handler) return Boolean;
216 -- See if the Handler has been "pragma"ed using Interrupt_Handler. Always
217 -- consider a null handler as registered.
219 --------------------
220 -- Attach_Handler --
221 --------------------
223 -- Calling this procedure with New_Handler = null and Static = True means
224 -- we want to detach the current handler regardless of the previous
225 -- handler's binding status (i.e. do not care if it is a dynamic or static
226 -- handler).
228 -- This option is needed so that during the finalization of a PO, we can
229 -- detach handlers attached through pragma Attach_Handler.
231 procedure Attach_Handler
232 (New_Handler : Parameterless_Handler;
233 Interrupt : Interrupt_ID;
234 Static : Boolean := False)
236 begin
237 if Is_Reserved (Interrupt) then
238 raise Program_Error with
239 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
240 end if;
242 Interrupt_Manager.Attach_Handler (New_Handler, Interrupt, Static);
244 end Attach_Handler;
246 -----------------------------
247 -- Bind_Interrupt_To_Entry --
248 -----------------------------
250 -- This procedure raises a Program_Error if it tries to bind an interrupt
251 -- to which an Entry or a Procedure is already bound.
253 procedure Bind_Interrupt_To_Entry
254 (T : Task_Id;
255 E : Task_Entry_Index;
256 Int_Ref : System.Address)
258 Interrupt : constant Interrupt_ID :=
259 Interrupt_ID (Storage_Elements.To_Integer (Int_Ref));
260 begin
261 if Is_Reserved (Interrupt) then
262 raise Program_Error with
263 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
264 end if;
266 Interrupt_Manager.Bind_Interrupt_To_Entry (T, E, Interrupt);
267 end Bind_Interrupt_To_Entry;
269 ---------------------
270 -- Block_Interrupt --
271 ---------------------
273 procedure Block_Interrupt (Interrupt : Interrupt_ID) is
274 begin
275 if Is_Reserved (Interrupt) then
276 raise Program_Error with
277 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
278 end if;
280 Interrupt_Manager.Block_Interrupt (Interrupt);
281 end Block_Interrupt;
283 ---------------------
284 -- Current_Handler --
285 ---------------------
287 function Current_Handler
288 (Interrupt : Interrupt_ID) return Parameterless_Handler
290 begin
291 if Is_Reserved (Interrupt) then
292 raise Program_Error with
293 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
294 end if;
296 -- ??? Since Parameterless_Handler is not Atomic, the current
297 -- implementation is wrong. We need a new service in Interrupt_Manager
298 -- to ensure atomicity.
300 return User_Handler (Interrupt).H;
301 end Current_Handler;
303 --------------------
304 -- Detach_Handler --
305 --------------------
307 -- Calling this procedure with Static = True means we want to Detach the
308 -- current handler regardless of the previous handler's binding status
309 -- (i.e. do not care if it is a dynamic or static handler).
311 -- This option is needed so that during the finalization of a PO, we can
312 -- detach handlers attached through pragma Attach_Handler.
314 procedure Detach_Handler
315 (Interrupt : Interrupt_ID;
316 Static : Boolean := False)
318 begin
319 if Is_Reserved (Interrupt) then
320 raise Program_Error with
321 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
322 end if;
324 Interrupt_Manager.Detach_Handler (Interrupt, Static);
325 end Detach_Handler;
327 ------------------------------
328 -- Detach_Interrupt_Entries --
329 ------------------------------
331 procedure Detach_Interrupt_Entries (T : Task_Id) is
332 begin
333 Interrupt_Manager.Detach_Interrupt_Entries (T);
334 end Detach_Interrupt_Entries;
336 ----------------------
337 -- Exchange_Handler --
338 ----------------------
340 -- Calling this procedure with New_Handler = null and Static = True means
341 -- we want to detach the current handler regardless of the previous
342 -- handler's binding status (i.e. do not care if it is a dynamic or static
343 -- handler).
345 -- This option is needed so that during the finalization of a PO, we can
346 -- detach handlers attached through pragma Attach_Handler.
348 procedure Exchange_Handler
349 (Old_Handler : out Parameterless_Handler;
350 New_Handler : Parameterless_Handler;
351 Interrupt : Interrupt_ID;
352 Static : Boolean := False)
354 begin
355 if Is_Reserved (Interrupt) then
356 raise Program_Error with
357 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
358 end if;
360 Interrupt_Manager.Exchange_Handler
361 (Old_Handler, New_Handler, Interrupt, Static);
362 end Exchange_Handler;
364 --------------
365 -- Finalize --
366 --------------
368 procedure Finalize (Object : in out Static_Interrupt_Protection) is
369 function State
370 (Int : System.Interrupt_Management.Interrupt_ID) return Character;
371 pragma Import (C, State, "__gnat_get_interrupt_state");
372 -- Get interrupt state for interrupt number Int. Defined in init.c
374 Default : constant Character := 's';
375 -- 's' Interrupt_State pragma set state to System (use "default"
376 -- system handler)
378 begin
379 -- ??? loop to be executed only when we're not doing library level
380 -- finalization, since in this case all interrupt tasks are gone.
382 -- If the Abort_Task signal is set to system, it means that we cannot
383 -- reset interrupt handlers since this would require sending the abort
384 -- signal to the Server_Task
386 if not Interrupt_Manager'Terminated
387 and then
388 State (System.Interrupt_Management.Abort_Task_Interrupt) /= Default
389 then
390 for N in reverse Object.Previous_Handlers'Range loop
391 Interrupt_Manager.Attach_Handler
392 (New_Handler => Object.Previous_Handlers (N).Handler,
393 Interrupt => Object.Previous_Handlers (N).Interrupt,
394 Static => Object.Previous_Handlers (N).Static,
395 Restoration => True);
396 end loop;
397 end if;
399 Tasking.Protected_Objects.Entries.Finalize
400 (Tasking.Protected_Objects.Entries.Protection_Entries (Object));
401 end Finalize;
403 -------------------------------------
404 -- Has_Interrupt_Or_Attach_Handler --
405 -------------------------------------
407 -- Need comments as to why these always return True ???
409 function Has_Interrupt_Or_Attach_Handler
410 (Object : access Dynamic_Interrupt_Protection) return Boolean
412 pragma Unreferenced (Object);
413 begin
414 return True;
415 end Has_Interrupt_Or_Attach_Handler;
417 function Has_Interrupt_Or_Attach_Handler
418 (Object : access Static_Interrupt_Protection) return Boolean
420 pragma Unreferenced (Object);
421 begin
422 return True;
423 end Has_Interrupt_Or_Attach_Handler;
425 ----------------------
426 -- Ignore_Interrupt --
427 ----------------------
429 procedure Ignore_Interrupt (Interrupt : Interrupt_ID) is
430 begin
431 if Is_Reserved (Interrupt) then
432 raise Program_Error with
433 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
434 end if;
436 Interrupt_Manager.Ignore_Interrupt (Interrupt);
437 end Ignore_Interrupt;
439 ----------------------
440 -- Install_Handlers --
441 ----------------------
443 procedure Install_Handlers
444 (Object : access Static_Interrupt_Protection;
445 New_Handlers : New_Handler_Array)
447 begin
448 for N in New_Handlers'Range loop
450 -- We need a lock around this ???
452 Object.Previous_Handlers (N).Interrupt := New_Handlers (N).Interrupt;
453 Object.Previous_Handlers (N).Static := User_Handler
454 (New_Handlers (N).Interrupt).Static;
456 -- We call Exchange_Handler and not directly Interrupt_Manager.
457 -- Exchange_Handler so we get the Is_Reserved check.
459 Exchange_Handler
460 (Old_Handler => Object.Previous_Handlers (N).Handler,
461 New_Handler => New_Handlers (N).Handler,
462 Interrupt => New_Handlers (N).Interrupt,
463 Static => True);
464 end loop;
465 end Install_Handlers;
467 ---------------------------------
468 -- Install_Restricted_Handlers --
469 ---------------------------------
471 procedure Install_Restricted_Handlers
472 (Prio : Interrupt_Priority;
473 Handlers : New_Handler_Array)
475 pragma Unreferenced (Prio);
476 begin
477 for N in Handlers'Range loop
478 Attach_Handler (Handlers (N).Handler, Handlers (N).Interrupt, True);
479 end loop;
480 end Install_Restricted_Handlers;
482 ----------------
483 -- Is_Blocked --
484 ----------------
486 function Is_Blocked (Interrupt : Interrupt_ID) return Boolean is
487 begin
488 if Is_Reserved (Interrupt) then
489 raise Program_Error with
490 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
491 end if;
493 return Blocked (Interrupt);
494 end Is_Blocked;
496 -----------------------
497 -- Is_Entry_Attached --
498 -----------------------
500 function Is_Entry_Attached (Interrupt : Interrupt_ID) return Boolean is
501 begin
502 if Is_Reserved (Interrupt) then
503 raise Program_Error with
504 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
505 end if;
507 return User_Entry (Interrupt).T /= Null_Task;
508 end Is_Entry_Attached;
510 -------------------------
511 -- Is_Handler_Attached --
512 -------------------------
514 function Is_Handler_Attached (Interrupt : Interrupt_ID) return Boolean is
515 begin
516 if Is_Reserved (Interrupt) then
517 raise Program_Error with
518 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
519 end if;
521 return User_Handler (Interrupt).H /= null;
522 end Is_Handler_Attached;
524 ----------------
525 -- Is_Ignored --
526 ----------------
528 function Is_Ignored (Interrupt : Interrupt_ID) return Boolean is
529 begin
530 if Is_Reserved (Interrupt) then
531 raise Program_Error with
532 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
533 end if;
535 return Ignored (Interrupt);
536 end Is_Ignored;
538 -------------------
539 -- Is_Registered --
540 -------------------
542 function Is_Registered (Handler : Parameterless_Handler) return Boolean is
543 Ptr : R_Link := Registered_Handlers;
545 type Acc_Proc is access procedure;
547 type Fat_Ptr is record
548 Object_Addr : System.Address;
549 Handler_Addr : Acc_Proc;
550 end record;
552 function To_Fat_Ptr is new Ada.Unchecked_Conversion
553 (Parameterless_Handler, Fat_Ptr);
555 Fat : Fat_Ptr;
557 begin
558 if Handler = null then
559 return True;
560 end if;
562 Fat := To_Fat_Ptr (Handler);
564 while Ptr /= null loop
565 if Ptr.H = Fat.Handler_Addr.all'Address then
566 return True;
567 end if;
569 Ptr := Ptr.Next;
570 end loop;
572 return False;
573 end Is_Registered;
575 -----------------
576 -- Is_Reserved --
577 -----------------
579 function Is_Reserved (Interrupt : Interrupt_ID) return Boolean is
580 begin
581 return IMNG.Reserve (IMNG.Interrupt_ID (Interrupt));
582 end Is_Reserved;
584 ---------------
585 -- Reference --
586 ---------------
588 function Reference (Interrupt : Interrupt_ID) return System.Address is
589 begin
590 if Is_Reserved (Interrupt) then
591 raise Program_Error with
592 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
593 end if;
595 return Storage_Elements.To_Address
596 (Storage_Elements.Integer_Address (Interrupt));
597 end Reference;
599 ---------------------------------
600 -- Register_Interrupt_Handler --
601 ---------------------------------
603 procedure Register_Interrupt_Handler (Handler_Addr : System.Address) is
604 begin
605 -- This routine registers the Handler as usable for Dynamic Interrupt
606 -- Handler. Routines attaching and detaching Handler dynamically should
607 -- first consult if the Handler is registered. A Program Error should
608 -- be raised if it is not registered.
610 -- The pragma Interrupt_Handler can only appear in the library level PO
611 -- definition and instantiation. Therefore, we do not need to implement
612 -- Unregistering operation. Neither we need to protect the queue
613 -- structure using a Lock.
615 pragma Assert (Handler_Addr /= System.Null_Address);
617 Registered_Handlers :=
618 new Registered_Handler'(H => Handler_Addr, Next => Registered_Handlers);
619 end Register_Interrupt_Handler;
621 -----------------------
622 -- Unblock_Interrupt --
623 -----------------------
625 procedure Unblock_Interrupt (Interrupt : Interrupt_ID) is
626 begin
627 if Is_Reserved (Interrupt) then
628 raise Program_Error with
629 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
630 end if;
632 Interrupt_Manager.Unblock_Interrupt (Interrupt);
633 end Unblock_Interrupt;
635 ------------------
636 -- Unblocked_By --
637 ------------------
639 function Unblocked_By
640 (Interrupt : Interrupt_ID) return System.Tasking.Task_Id
642 begin
643 if Is_Reserved (Interrupt) then
644 raise Program_Error with
645 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
646 end if;
648 return Last_Unblocker (Interrupt);
649 end Unblocked_By;
651 ------------------------
652 -- Unignore_Interrupt --
653 ------------------------
655 procedure Unignore_Interrupt (Interrupt : Interrupt_ID) is
656 begin
657 if Is_Reserved (Interrupt) then
658 raise Program_Error with
659 "interrupt" & Interrupt_ID'Image (Interrupt) & " is reserved";
660 end if;
662 Interrupt_Manager.Unignore_Interrupt (Interrupt);
663 end Unignore_Interrupt;
665 -----------------------
666 -- Interrupt_Manager --
667 -----------------------
669 task body Interrupt_Manager is
670 -- By making this task independent of master, when the process
671 -- goes away, the Interrupt_Manager will terminate gracefully.
673 Ignore : constant Boolean := System.Tasking.Utilities.Make_Independent;
675 ---------------------
676 -- Local Variables --
677 ---------------------
679 Intwait_Mask : aliased IMNG.Interrupt_Mask;
680 Ret_Interrupt : Interrupt_ID;
681 Old_Mask : aliased IMNG.Interrupt_Mask;
682 Old_Handler : Parameterless_Handler;
684 --------------------
685 -- Local Routines --
686 --------------------
688 procedure Bind_Handler (Interrupt : Interrupt_ID);
689 -- This procedure does not do anything if the Interrupt is blocked.
690 -- Otherwise, we have to interrupt Server_Task for status change through
691 -- Wakeup interrupt.
693 procedure Unbind_Handler (Interrupt : Interrupt_ID);
694 -- This procedure does not do anything if the Interrupt is blocked.
695 -- Otherwise, we have to interrupt Server_Task for status change
696 -- through abort interrupt.
698 procedure Unprotected_Exchange_Handler
699 (Old_Handler : out Parameterless_Handler;
700 New_Handler : Parameterless_Handler;
701 Interrupt : Interrupt_ID;
702 Static : Boolean;
703 Restoration : Boolean := False);
705 procedure Unprotected_Detach_Handler
706 (Interrupt : Interrupt_ID;
707 Static : Boolean);
709 ------------------
710 -- Bind_Handler --
711 ------------------
713 procedure Bind_Handler (Interrupt : Interrupt_ID) is
714 begin
715 if not Blocked (Interrupt) then
717 -- Mask this task for the given Interrupt so that all tasks
718 -- are masked for the Interrupt and the actual delivery of the
719 -- Interrupt will be caught using "sigwait" by the
720 -- corresponding Server_Task.
722 IMOP.Thread_Block_Interrupt (IMNG.Interrupt_ID (Interrupt));
724 -- We have installed a Handler or an Entry before we called
725 -- this procedure. If the Handler Task is waiting to be awakened,
726 -- do it here. Otherwise, the interrupt will be discarded.
728 POP.Wakeup (Server_ID (Interrupt), Interrupt_Server_Idle_Sleep);
729 end if;
730 end Bind_Handler;
732 --------------------
733 -- Unbind_Handler --
734 --------------------
736 procedure Unbind_Handler (Interrupt : Interrupt_ID) is
737 Server : System.Tasking.Task_Id;
739 begin
740 if not Blocked (Interrupt) then
742 -- Currently, there is a Handler or an Entry attached and
743 -- corresponding Server_Task is waiting on "sigwait." We have to
744 -- wake up the Server_Task and make it wait on condition variable
745 -- by sending an Abort_Task_Interrupt
747 Server := Server_ID (Interrupt);
749 case Server.Common.State is
750 when Interrupt_Server_Blocked_Interrupt_Sleep
751 | Interrupt_Server_Idle_Sleep
753 POP.Wakeup (Server, Server.Common.State);
755 when Interrupt_Server_Blocked_On_Event_Flag =>
756 POP.Abort_Task (Server);
758 -- Make sure corresponding Server_Task is out of its
759 -- own sigwait state.
761 Ret_Interrupt :=
762 Interrupt_ID (IMOP.Interrupt_Wait (Intwait_Mask'Access));
763 pragma Assert
764 (Ret_Interrupt = Interrupt_ID (IMNG.Abort_Task_Interrupt));
766 when Runnable =>
767 null;
769 when others =>
770 pragma Assert (Standard.False);
771 null;
772 end case;
774 IMOP.Install_Default_Action (IMNG.Interrupt_ID (Interrupt));
776 -- Unmake the Interrupt for this task in order to allow default
777 -- action again.
779 IMOP.Thread_Unblock_Interrupt (IMNG.Interrupt_ID (Interrupt));
781 else
782 IMOP.Install_Default_Action (IMNG.Interrupt_ID (Interrupt));
783 end if;
784 end Unbind_Handler;
786 --------------------------------
787 -- Unprotected_Detach_Handler --
788 --------------------------------
790 procedure Unprotected_Detach_Handler
791 (Interrupt : Interrupt_ID;
792 Static : Boolean)
794 Old_Handler : Parameterless_Handler;
796 begin
797 if User_Entry (Interrupt).T /= Null_Task then
799 -- In case we have an Interrupt Entry installed, raise a program
800 -- error, (propagate it to the caller).
802 raise Program_Error with
803 "an interrupt entry is already installed";
804 end if;
806 -- Note : Static = True will pass the following check. That is the
807 -- case when we want to detach a handler regardless of the static
808 -- status of the current_Handler.
810 if not Static and then User_Handler (Interrupt).Static then
812 -- Tries to detach a static Interrupt Handler.
813 -- raise a program error.
815 raise Program_Error with
816 "trying to detach a static interrupt handler";
817 end if;
819 -- The interrupt should no longer be ignored if
820 -- it was ever ignored.
822 Ignored (Interrupt) := False;
824 Old_Handler := User_Handler (Interrupt).H;
826 -- The new handler
828 User_Handler (Interrupt).H := null;
829 User_Handler (Interrupt).Static := False;
831 if Old_Handler /= null then
832 Unbind_Handler (Interrupt);
833 end if;
834 end Unprotected_Detach_Handler;
836 ----------------------------------
837 -- Unprotected_Exchange_Handler --
838 ----------------------------------
840 procedure Unprotected_Exchange_Handler
841 (Old_Handler : out Parameterless_Handler;
842 New_Handler : Parameterless_Handler;
843 Interrupt : Interrupt_ID;
844 Static : Boolean;
845 Restoration : Boolean := False)
847 begin
848 if User_Entry (Interrupt).T /= Null_Task then
850 -- In case we have an Interrupt Entry already installed, raise a
851 -- program error, (propagate it to the caller).
853 raise Program_Error with
854 "an interrupt is already installed";
855 end if;
857 -- Note : A null handler with Static = True will pass the following
858 -- check. That is the case when we want to Detach a handler
859 -- regardless of the Static status of the current_Handler.
861 -- We don't check anything if Restoration is True, since we may be
862 -- detaching a static handler to restore a dynamic one.
864 if not Restoration and then not Static
866 -- Tries to overwrite a static Interrupt Handler with a dynamic
867 -- Handler
869 and then (User_Handler (Interrupt).Static
871 -- The new handler is not specified as an
872 -- Interrupt Handler by a pragma.
874 or else not Is_Registered (New_Handler))
875 then
876 raise Program_Error with
877 "trying to overwrite a static Interrupt Handler with a " &
878 "dynamic handler";
879 end if;
881 -- The interrupt should no longer be ignored if
882 -- it was ever ignored.
884 Ignored (Interrupt) := False;
886 -- Save the old handler
888 Old_Handler := User_Handler (Interrupt).H;
890 -- The new handler
892 User_Handler (Interrupt).H := New_Handler;
894 if New_Handler = null then
896 -- The null handler means we are detaching the handler
898 User_Handler (Interrupt).Static := False;
900 else
901 User_Handler (Interrupt).Static := Static;
902 end if;
904 -- Invoke a corresponding Server_Task if not yet created.
905 -- Place Task_Id info in Server_ID array.
907 if Server_ID (Interrupt) = Null_Task then
909 -- When a new Server_Task is created, it should have its
910 -- signal mask set to the All_Tasks_Mask.
912 IMOP.Set_Interrupt_Mask
913 (IMOP.All_Tasks_Mask'Access, Old_Mask'Access);
914 Access_Hold := new Server_Task (Interrupt);
915 IMOP.Set_Interrupt_Mask (Old_Mask'Access);
917 Server_ID (Interrupt) := To_System (Access_Hold.all'Identity);
918 end if;
920 if New_Handler = null then
921 if Old_Handler /= null then
922 Unbind_Handler (Interrupt);
923 end if;
925 return;
926 end if;
928 if Old_Handler = null then
929 Bind_Handler (Interrupt);
930 end if;
931 end Unprotected_Exchange_Handler;
933 -- Start of processing for Interrupt_Manager
935 begin
936 -- Environment task gets its own interrupt mask, saves it, and then
937 -- masks all interrupts except the Keep_Unmasked set.
939 -- During rendezvous, the Interrupt_Manager receives the old interrupt
940 -- mask of the environment task, and sets its own interrupt mask to that
941 -- value.
943 -- The environment task will call the entry of Interrupt_Manager some
944 -- during elaboration of the body of this package.
946 accept Initialize (Mask : IMNG.Interrupt_Mask) do
947 declare
948 The_Mask : aliased IMNG.Interrupt_Mask;
949 begin
950 IMOP.Copy_Interrupt_Mask (The_Mask, Mask);
951 IMOP.Set_Interrupt_Mask (The_Mask'Access);
952 end;
953 end Initialize;
955 -- Note: All tasks in RTS will have all the Reserve Interrupts being
956 -- masked (except the Interrupt_Manager) and Keep_Unmasked unmasked
957 -- when created.
959 -- Abort_Task_Interrupt is one of the Interrupt unmasked in all tasks.
960 -- We mask the Interrupt in this particular task so that "sigwait" is
961 -- possible to catch an explicitly sent Abort_Task_Interrupt from the
962 -- Server_Tasks.
964 -- This sigwaiting is needed so that we make sure a Server_Task is out
965 -- of its own sigwait state. This extra synchronization is necessary to
966 -- prevent following scenarios.
968 -- 1) Interrupt_Manager sends an Abort_Task_Interrupt to the
969 -- Server_Task then changes its own interrupt mask (OS level).
970 -- If an interrupt (corresponding to the Server_Task) arrives
971 -- in the mean time we have the Interrupt_Manager unmasked and
972 -- the Server_Task waiting on sigwait.
974 -- 2) For unbinding handler, we install a default action in the
975 -- Interrupt_Manager. POSIX.1c states that the result of using
976 -- "sigwait" and "sigaction" simultaneously on the same interrupt
977 -- is undefined. Therefore, we need to be informed from the
978 -- Server_Task of the fact that the Server_Task is out of its
979 -- sigwait stage.
981 IMOP.Empty_Interrupt_Mask (Intwait_Mask'Access);
982 IMOP.Add_To_Interrupt_Mask
983 (Intwait_Mask'Access, IMNG.Abort_Task_Interrupt);
984 IMOP.Thread_Block_Interrupt
985 (IMNG.Abort_Task_Interrupt);
987 loop
988 -- A block is needed to absorb Program_Error exception
990 begin
991 select
992 accept Attach_Handler
993 (New_Handler : Parameterless_Handler;
994 Interrupt : Interrupt_ID;
995 Static : Boolean;
996 Restoration : Boolean := False)
998 Unprotected_Exchange_Handler
999 (Old_Handler, New_Handler, Interrupt, Static, Restoration);
1000 end Attach_Handler;
1003 accept Exchange_Handler
1004 (Old_Handler : out Parameterless_Handler;
1005 New_Handler : Parameterless_Handler;
1006 Interrupt : Interrupt_ID;
1007 Static : Boolean)
1009 Unprotected_Exchange_Handler
1010 (Old_Handler, New_Handler, Interrupt, Static);
1011 end Exchange_Handler;
1014 accept Detach_Handler
1015 (Interrupt : Interrupt_ID;
1016 Static : Boolean)
1018 Unprotected_Detach_Handler (Interrupt, Static);
1019 end Detach_Handler;
1022 accept Bind_Interrupt_To_Entry
1023 (T : Task_Id;
1024 E : Task_Entry_Index;
1025 Interrupt : Interrupt_ID)
1027 -- If there is a binding already (either a procedure or an
1028 -- entry), raise Program_Error (propagate it to the caller).
1030 if User_Handler (Interrupt).H /= null
1031 or else User_Entry (Interrupt).T /= Null_Task
1032 then
1033 raise Program_Error with
1034 "a binding for this interrupt is already present";
1035 end if;
1037 -- The interrupt should no longer be ignored if
1038 -- it was ever ignored.
1040 Ignored (Interrupt) := False;
1041 User_Entry (Interrupt) := Entry_Assoc'(T => T, E => E);
1043 -- Indicate the attachment of Interrupt Entry in ATCB.
1044 -- This is need so that when an Interrupt Entry task
1045 -- terminates the binding can be cleaned. The call to
1046 -- unbinding must be made by the task before it terminates.
1048 T.Interrupt_Entry := True;
1050 -- Invoke a corresponding Server_Task if not yet created.
1051 -- Place Task_Id info in Server_ID array.
1053 if Server_ID (Interrupt) = Null_Task then
1055 -- When a new Server_Task is created, it should have its
1056 -- signal mask set to the All_Tasks_Mask.
1058 IMOP.Set_Interrupt_Mask
1059 (IMOP.All_Tasks_Mask'Access, Old_Mask'Access);
1060 Access_Hold := new Server_Task (Interrupt);
1061 IMOP.Set_Interrupt_Mask (Old_Mask'Access);
1062 Server_ID (Interrupt) :=
1063 To_System (Access_Hold.all'Identity);
1064 end if;
1066 Bind_Handler (Interrupt);
1067 end Bind_Interrupt_To_Entry;
1070 accept Detach_Interrupt_Entries (T : Task_Id) do
1071 for J in Interrupt_ID'Range loop
1072 if not Is_Reserved (J) then
1073 if User_Entry (J).T = T then
1075 -- The interrupt should no longer be ignored if
1076 -- it was ever ignored.
1078 Ignored (J) := False;
1079 User_Entry (J) := Entry_Assoc'
1080 (T => Null_Task, E => Null_Task_Entry);
1081 Unbind_Handler (J);
1082 end if;
1083 end if;
1084 end loop;
1086 -- Indicate in ATCB that no Interrupt Entries are attached
1088 T.Interrupt_Entry := False;
1089 end Detach_Interrupt_Entries;
1092 accept Block_Interrupt (Interrupt : Interrupt_ID) do
1093 if Blocked (Interrupt) then
1094 return;
1095 end if;
1097 Blocked (Interrupt) := True;
1098 Last_Unblocker (Interrupt) := Null_Task;
1100 -- Mask this task for the given Interrupt so that all tasks
1101 -- are masked for the Interrupt.
1103 IMOP.Thread_Block_Interrupt (IMNG.Interrupt_ID (Interrupt));
1105 if User_Handler (Interrupt).H /= null
1106 or else User_Entry (Interrupt).T /= Null_Task
1107 then
1108 -- This is the case where the Server_Task
1109 -- is waiting on"sigwait." Wake it up by sending an
1110 -- Abort_Task_Interrupt so that the Server_Task waits
1111 -- on Cond.
1113 POP.Abort_Task (Server_ID (Interrupt));
1115 -- Make sure corresponding Server_Task is out of its own
1116 -- sigwait state.
1118 Ret_Interrupt := Interrupt_ID
1119 (IMOP.Interrupt_Wait (Intwait_Mask'Access));
1120 pragma Assert
1121 (Ret_Interrupt =
1122 Interrupt_ID (IMNG.Abort_Task_Interrupt));
1123 end if;
1124 end Block_Interrupt;
1127 accept Unblock_Interrupt (Interrupt : Interrupt_ID) do
1128 if not Blocked (Interrupt) then
1129 return;
1130 end if;
1132 Blocked (Interrupt) := False;
1133 Last_Unblocker (Interrupt) :=
1134 To_System (Unblock_Interrupt'Caller);
1136 if User_Handler (Interrupt).H = null
1137 and then User_Entry (Interrupt).T = Null_Task
1138 then
1139 -- No handler is attached. Unmask the Interrupt so that
1140 -- the default action can be carried out.
1142 IMOP.Thread_Unblock_Interrupt
1143 (IMNG.Interrupt_ID (Interrupt));
1145 else
1146 -- The Server_Task must be waiting on the Cond variable
1147 -- since it was being blocked and an Interrupt Hander or
1148 -- an Entry was there. Wake it up and let it change it
1149 -- place of waiting according to its new state.
1151 POP.Wakeup (Server_ID (Interrupt),
1152 Interrupt_Server_Blocked_Interrupt_Sleep);
1153 end if;
1154 end Unblock_Interrupt;
1157 accept Ignore_Interrupt (Interrupt : Interrupt_ID) do
1158 if Ignored (Interrupt) then
1159 return;
1160 end if;
1162 Ignored (Interrupt) := True;
1164 -- If there is a handler associated with the Interrupt,
1165 -- detach it first. In this way we make sure that the
1166 -- Server_Task is not on sigwait. This is legal since
1167 -- Unignore_Interrupt is to install the default action.
1169 if User_Handler (Interrupt).H /= null then
1170 Unprotected_Detach_Handler
1171 (Interrupt => Interrupt, Static => True);
1173 elsif User_Entry (Interrupt).T /= Null_Task then
1174 User_Entry (Interrupt) := Entry_Assoc'
1175 (T => Null_Task, E => Null_Task_Entry);
1176 Unbind_Handler (Interrupt);
1177 end if;
1179 IMOP.Install_Ignore_Action (IMNG.Interrupt_ID (Interrupt));
1180 end Ignore_Interrupt;
1183 accept Unignore_Interrupt (Interrupt : Interrupt_ID) do
1184 Ignored (Interrupt) := False;
1186 -- If there is a handler associated with the Interrupt,
1187 -- detach it first. In this way we make sure that the
1188 -- Server_Task is not on sigwait. This is legal since
1189 -- Unignore_Interrupt is to install the default action.
1191 if User_Handler (Interrupt).H /= null then
1192 Unprotected_Detach_Handler
1193 (Interrupt => Interrupt, Static => True);
1195 elsif User_Entry (Interrupt).T /= Null_Task then
1196 User_Entry (Interrupt) := Entry_Assoc'
1197 (T => Null_Task, E => Null_Task_Entry);
1198 Unbind_Handler (Interrupt);
1199 end if;
1201 IMOP.Install_Default_Action (IMNG.Interrupt_ID (Interrupt));
1202 end Unignore_Interrupt;
1203 end select;
1205 exception
1206 -- If there is a program error we just want to propagate it to
1207 -- the caller and do not want to stop this task.
1209 when Program_Error =>
1210 null;
1212 when X : others =>
1213 System.IO.Put_Line ("Exception in Interrupt_Manager");
1214 System.IO.Put_Line (Ada.Exceptions.Exception_Information (X));
1215 pragma Assert (Standard.False);
1216 end;
1217 end loop;
1218 end Interrupt_Manager;
1220 -----------------
1221 -- Server_Task --
1222 -----------------
1224 task body Server_Task is
1225 -- By making this task independent of master, when the process goes
1226 -- away, the Server_Task will terminate gracefully.
1228 Ignore : constant Boolean := System.Tasking.Utilities.Make_Independent;
1230 Intwait_Mask : aliased IMNG.Interrupt_Mask;
1231 Ret_Interrupt : Interrupt_ID;
1232 Self_ID : constant Task_Id := Self;
1233 Tmp_Handler : Parameterless_Handler;
1234 Tmp_ID : Task_Id;
1235 Tmp_Entry_Index : Task_Entry_Index;
1237 begin
1238 -- Install default action in system level
1240 IMOP.Install_Default_Action (IMNG.Interrupt_ID (Interrupt));
1242 -- Note: All tasks in RTS will have all the Reserve Interrupts being
1243 -- masked (except the Interrupt_Manager) and Keep_Unmasked unmasked when
1244 -- created.
1246 -- Abort_Task_Interrupt is one of the Interrupt unmasked in all tasks.
1247 -- We mask the Interrupt in this particular task so that "sigwait" is
1248 -- possible to catch an explicitly sent Abort_Task_Interrupt from the
1249 -- Interrupt_Manager.
1251 -- There are two Interrupt interrupts that this task catch through
1252 -- "sigwait." One is the Interrupt this task is designated to catch
1253 -- in order to execute user handler or entry. The other one is
1254 -- the Abort_Task_Interrupt. This interrupt is being sent from the
1255 -- Interrupt_Manager to inform status changes (e.g: become Blocked,
1256 -- Handler or Entry is to be detached).
1258 -- Prepare a mask to used for sigwait
1260 IMOP.Empty_Interrupt_Mask (Intwait_Mask'Access);
1262 IMOP.Add_To_Interrupt_Mask
1263 (Intwait_Mask'Access, IMNG.Interrupt_ID (Interrupt));
1265 IMOP.Add_To_Interrupt_Mask
1266 (Intwait_Mask'Access, IMNG.Abort_Task_Interrupt);
1268 IMOP.Thread_Block_Interrupt
1269 (IMNG.Abort_Task_Interrupt);
1271 PIO.Set_Interrupt_ID (IMNG.Interrupt_ID (Interrupt), Self_ID);
1273 loop
1274 System.Tasking.Initialization.Defer_Abort (Self_ID);
1275 POP.Write_Lock (Self_ID);
1277 if User_Handler (Interrupt).H = null
1278 and then User_Entry (Interrupt).T = Null_Task
1279 then
1280 -- No Interrupt binding. If there is an interrupt,
1281 -- Interrupt_Manager will take default action.
1283 Self_ID.Common.State := Interrupt_Server_Blocked_Interrupt_Sleep;
1284 POP.Sleep (Self_ID, Interrupt_Server_Idle_Sleep);
1285 Self_ID.Common.State := Runnable;
1287 elsif Blocked (Interrupt) then
1289 -- Interrupt is blocked, stay here, so we won't catch it
1291 Self_ID.Common.State := Interrupt_Server_Blocked_Interrupt_Sleep;
1292 POP.Sleep (Self_ID, Interrupt_Server_Blocked_Interrupt_Sleep);
1293 Self_ID.Common.State := Runnable;
1295 else
1296 -- A Handler or an Entry is installed. At this point all tasks
1297 -- mask for the Interrupt is masked. Catch the Interrupt using
1298 -- sigwait.
1300 -- This task may wake up from sigwait by receiving an interrupt
1301 -- (Abort_Task_Interrupt) from the Interrupt_Manager for unbinding
1302 -- a Procedure Handler or an Entry. Or it could be a wake up
1303 -- from status change (Unblocked -> Blocked). If that is not
1304 -- the case, we should execute the attached Procedure or Entry.
1306 Self_ID.Common.State := Interrupt_Server_Blocked_On_Event_Flag;
1307 POP.Unlock (Self_ID);
1309 -- Avoid race condition when terminating application and
1310 -- System.Parameters.No_Abort is True.
1312 if Parameters.No_Abort and then Self_ID.Pending_Action then
1313 Initialization.Do_Pending_Action (Self_ID);
1314 end if;
1316 Ret_Interrupt :=
1317 Interrupt_ID (IMOP.Interrupt_Wait (Intwait_Mask'Access));
1318 Self_ID.Common.State := Runnable;
1320 if Ret_Interrupt = Interrupt_ID (IMNG.Abort_Task_Interrupt) then
1322 -- Inform the Interrupt_Manager of wakeup from above sigwait
1324 POP.Abort_Task (Interrupt_Manager_ID);
1325 POP.Write_Lock (Self_ID);
1327 else
1328 POP.Write_Lock (Self_ID);
1330 if Ret_Interrupt /= Interrupt then
1332 -- On some systems (e.g. recent linux kernels), sigwait
1333 -- may return unexpectedly (with errno set to EINTR).
1335 null;
1337 else
1338 -- Even though we have received an Interrupt the status may
1339 -- have changed already before we got the Self_ID lock above
1340 -- Therefore we make sure a Handler or an Entry is still
1341 -- there and make appropriate call.
1343 -- If there is no calls to make we need to regenerate the
1344 -- Interrupt in order not to lose it.
1346 if User_Handler (Interrupt).H /= null then
1347 Tmp_Handler := User_Handler (Interrupt).H;
1349 -- RTS calls should not be made with self being locked
1351 POP.Unlock (Self_ID);
1352 Tmp_Handler.all;
1353 POP.Write_Lock (Self_ID);
1355 elsif User_Entry (Interrupt).T /= Null_Task then
1356 Tmp_ID := User_Entry (Interrupt).T;
1357 Tmp_Entry_Index := User_Entry (Interrupt).E;
1359 -- RTS calls should not be made with self being locked
1361 POP.Unlock (Self_ID);
1363 System.Tasking.Rendezvous.Call_Simple
1364 (Tmp_ID, Tmp_Entry_Index, System.Null_Address);
1366 POP.Write_Lock (Self_ID);
1368 else
1369 -- This is a situation that this task wakes up receiving
1370 -- an Interrupt and before it gets the lock the Interrupt
1371 -- is blocked. We do not want to lose the interrupt in
1372 -- this case so we regenerate the Interrupt to process
1373 -- level.
1375 IMOP.Interrupt_Self_Process
1376 (IMNG.Interrupt_ID (Interrupt));
1377 end if;
1378 end if;
1379 end if;
1380 end if;
1382 POP.Unlock (Self_ID);
1383 System.Tasking.Initialization.Undefer_Abort (Self_ID);
1385 if Self_ID.Pending_Action then
1386 Initialization.Do_Pending_Action (Self_ID);
1387 end if;
1389 -- Undefer abort here to allow a window for this task to be aborted
1390 -- at the time of system shutdown. We also explicitly test for
1391 -- Pending_Action in case System.Parameters.No_Abort is True.
1393 end loop;
1394 end Server_Task;
1396 -- Elaboration code for package System.Interrupts
1398 begin
1399 -- Get Interrupt_Manager's ID so that Abort_Interrupt can be sent
1401 Interrupt_Manager_ID := To_System (Interrupt_Manager'Identity);
1403 -- During the elaboration of this package body we want the RTS
1404 -- to inherit the interrupt mask from the Environment Task.
1406 IMOP.Setup_Interrupt_Mask;
1408 -- The environment task should have gotten its mask from the enclosing
1409 -- process during the RTS start up. (See processing in s-inmaop.adb). Pass
1410 -- the Interrupt_Mask of the environment task to the Interrupt_Manager.
1412 -- Note: At this point we know that all tasks are masked for non-reserved
1413 -- signals. Only the Interrupt_Manager will have masks set up differently
1414 -- inheriting the original environment task's mask.
1416 Interrupt_Manager.Initialize (IMOP.Environment_Mask);
1417 end System.Interrupts;