1 ------------------------------------------------------------------------------
3 -- GNAT RUN-TIME LIBRARY (GNARL) COMPONENTS --
5 -- S Y S T E M . I N T E R R U P T S --
9 -- Copyright (C) 1992-2011, Free Software Foundation, Inc. --
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. --
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. --
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/>. --
27 -- GNARL was developed by the GNARL team at Florida State University. --
28 -- Extensive contributions were provided by Ada Core Technologies, Inc. --
30 ------------------------------------------------------------------------------
34 -- All user-handleable signals are masked at all times in all tasks/threads
35 -- except possibly for the Interrupt_Manager task.
37 -- When a user task wants to have the effect of masking/unmasking an signal,
38 -- it must call Block_Interrupt/Unblock_Interrupt, which will have the effect
39 -- of unmasking/masking the signal in the Interrupt_Manager task. These
40 -- comments do not apply to vectored hardware interrupts, which may be masked
41 -- or unmasked using routined interfaced to the relevant embedded RTOS system
44 -- Once we associate a Signal_Server_Task with an signal, the task never goes
45 -- away, and we never remove the association. On the other hand, it is more
46 -- convenient to terminate an associated Interrupt_Server_Task for a vectored
47 -- hardware interrupt (since we use a binary semaphore for synchronization
48 -- with the umbrella handler).
50 -- There is no more than one signal per Signal_Server_Task and no more than
51 -- one Signal_Server_Task per signal. The same relation holds for hardware
52 -- interrupts and Interrupt_Server_Task's at any given time. That is, only
53 -- one non-terminated Interrupt_Server_Task exists for a give interrupt at
56 -- Within this package, the lock L is used to protect the various status
57 -- tables. If there is a Server_Task associated with a signal or interrupt, we
58 -- use the per-task lock of the Server_Task instead so that we protect the
59 -- status between Interrupt_Manager and Server_Task. Protection among service
60 -- requests are ensured via user calls to the Interrupt_Manager entries.
62 -- This is reasonably generic version of this package, supporting vectored
63 -- hardware interrupts using non-RTOS specific adapter routines which
64 -- should easily implemented on any RTOS capable of supporting GNAT.
66 with Ada
.Unchecked_Conversion
;
67 with Ada
.Task_Identification
;
69 with Interfaces
.C
; use Interfaces
.C
;
70 with System
.OS_Interface
; use System
.OS_Interface
;
71 with System
.Interrupt_Management
;
72 with System
.Task_Primitives
.Operations
;
73 with System
.Storage_Elements
;
74 with System
.Tasking
.Utilities
;
76 with System
.Tasking
.Rendezvous
;
77 pragma Elaborate_All
(System
.Tasking
.Rendezvous
);
79 package body System
.Interrupts
is
83 package POP
renames System
.Task_Primitives
.Operations
;
85 function To_Ada
is new Ada
.Unchecked_Conversion
86 (System
.Tasking
.Task_Id
, Ada
.Task_Identification
.Task_Id
);
88 function To_System
is new Ada
.Unchecked_Conversion
89 (Ada
.Task_Identification
.Task_Id
, Task_Id
);
95 -- WARNING: System.Tasking.Stages performs calls to this task with
96 -- low-level constructs. Do not change this spec without synchronizing it.
98 task Interrupt_Manager
is
99 entry Detach_Interrupt_Entries
(T
: Task_Id
);
102 (New_Handler
: Parameterless_Handler
;
103 Interrupt
: Interrupt_ID
;
105 Restoration
: Boolean := False);
107 entry Exchange_Handler
108 (Old_Handler
: out Parameterless_Handler
;
109 New_Handler
: Parameterless_Handler
;
110 Interrupt
: Interrupt_ID
;
114 (Interrupt
: Interrupt_ID
;
117 entry Bind_Interrupt_To_Entry
119 E
: Task_Entry_Index
;
120 Interrupt
: Interrupt_ID
);
122 pragma Interrupt_Priority
(System
.Interrupt_Priority
'First);
123 end Interrupt_Manager
;
125 task type Interrupt_Server_Task
126 (Interrupt
: Interrupt_ID
; Int_Sema
: Binary_Semaphore_Id
) is
127 -- Server task for vectored hardware interrupt handling
128 pragma Interrupt_Priority
(System
.Interrupt_Priority
'First + 2);
129 end Interrupt_Server_Task
;
131 type Interrupt_Task_Access
is access Interrupt_Server_Task
;
133 -------------------------------
134 -- Local Types and Variables --
135 -------------------------------
137 type Entry_Assoc
is record
139 E
: Task_Entry_Index
;
142 type Handler_Assoc
is record
143 H
: Parameterless_Handler
;
144 Static
: Boolean; -- Indicates static binding;
147 User_Handler
: array (Interrupt_ID
) of Handler_Assoc
:=
148 (others => (null, Static
=> False));
149 pragma Volatile_Components
(User_Handler
);
150 -- Holds the protected procedure handler (if any) and its Static
151 -- information for each interrupt or signal. A handler is static
152 -- iff it is specified through the pragma Attach_Handler.
154 User_Entry
: array (Interrupt_ID
) of Entry_Assoc
:=
155 (others => (T
=> Null_Task
, E
=> Null_Task_Entry
));
156 pragma Volatile_Components
(User_Entry
);
157 -- Holds the task and entry index (if any) for each interrupt / signal
159 -- Type and Head, Tail of the list containing Registered Interrupt
160 -- Handlers. These definitions are used to register the handlers
161 -- specified by the pragma Interrupt_Handler.
163 type Registered_Handler
;
164 type R_Link
is access all Registered_Handler
;
166 type Registered_Handler
is record
167 H
: System
.Address
:= System
.Null_Address
;
168 Next
: R_Link
:= null;
171 Registered_Handler_Head
: R_Link
:= null;
172 Registered_Handler_Tail
: R_Link
:= null;
174 Server_ID
: array (Interrupt_ID
) of System
.Tasking
.Task_Id
:=
175 (others => System
.Tasking
.Null_Task
);
176 pragma Atomic_Components
(Server_ID
);
177 -- Holds the Task_Id of the Server_Task for each interrupt / signal.
178 -- Task_Id is needed to accomplish locking per interrupt base. Also
179 -- is needed to determine whether to create a new Server_Task.
181 Semaphore_ID_Map
: array
182 (Interrupt_ID
range 0 .. System
.OS_Interface
.Max_HW_Interrupt
)
183 of Binary_Semaphore_Id
:= (others => 0);
184 -- Array of binary semaphores associated with vectored interrupts
185 -- Note that the last bound should be Max_HW_Interrupt, but this will raise
186 -- Storage_Error if Num_HW_Interrupts is null, so use an extra 4 bytes
189 Interrupt_Access_Hold
: Interrupt_Task_Access
;
190 -- Variable for allocating an Interrupt_Server_Task
192 Handler_Installed
: array (HW_Interrupt
) of Boolean := (others => False);
193 -- True if Notify_Interrupt was connected to the interrupt. Handlers
194 -- can be connected but disconnection is not possible on VxWorks.
195 -- Therefore we ensure Notify_Installed is connected at most once.
197 -----------------------
198 -- Local Subprograms --
199 -----------------------
201 procedure Check_Reserved_Interrupt
(Interrupt
: Interrupt_ID
);
202 -- Check if Id is a reserved interrupt, and if so raise Program_Error
203 -- with an appropriate message, otherwise return.
205 procedure Finalize_Interrupt_Servers
;
206 -- Unbind the handlers for hardware interrupt server tasks at program
209 function Is_Registered
(Handler
: Parameterless_Handler
) return Boolean;
210 -- See if Handler has been "pragma"ed using Interrupt_Handler.
211 -- Always consider a null handler as registered.
213 procedure Notify_Interrupt
(Param
: System
.Address
);
214 pragma Convention
(C
, Notify_Interrupt
);
215 -- Umbrella handler for vectored interrupts (not signals)
217 procedure Install_Umbrella_Handler
218 (Interrupt
: HW_Interrupt
;
219 Handler
: System
.OS_Interface
.Interrupt_Handler
);
220 -- Install the runtime umbrella handler for a vectored hardware
223 procedure Unimplemented
(Feature
: String);
224 pragma No_Return
(Unimplemented
);
225 -- Used to mark a call to an unimplemented function. Raises Program_Error
226 -- with an appropriate message noting that Feature is unimplemented.
232 -- Calling this procedure with New_Handler = null and Static = True
233 -- means we want to detach the current handler regardless of the
234 -- previous handler's binding status (i.e. do not care if it is a
235 -- dynamic or static handler).
237 -- This option is needed so that during the finalization of a PO, we
238 -- can detach handlers attached through pragma Attach_Handler.
240 procedure Attach_Handler
241 (New_Handler
: Parameterless_Handler
;
242 Interrupt
: Interrupt_ID
;
243 Static
: Boolean := False) is
245 Check_Reserved_Interrupt
(Interrupt
);
246 Interrupt_Manager
.Attach_Handler
(New_Handler
, Interrupt
, Static
);
249 -----------------------------
250 -- Bind_Interrupt_To_Entry --
251 -----------------------------
253 -- This procedure raises a Program_Error if it tries to
254 -- bind an interrupt to which an Entry or a Procedure is
257 procedure Bind_Interrupt_To_Entry
259 E
: Task_Entry_Index
;
260 Int_Ref
: System
.Address
)
262 Interrupt
: constant Interrupt_ID
:=
263 Interrupt_ID
(Storage_Elements
.To_Integer
(Int_Ref
));
266 Check_Reserved_Interrupt
(Interrupt
);
267 Interrupt_Manager
.Bind_Interrupt_To_Entry
(T
, E
, Interrupt
);
268 end Bind_Interrupt_To_Entry
;
270 ---------------------
271 -- Block_Interrupt --
272 ---------------------
274 procedure Block_Interrupt
(Interrupt
: Interrupt_ID
) is
276 Unimplemented
("Block_Interrupt");
279 ------------------------------
280 -- Check_Reserved_Interrupt --
281 ------------------------------
283 procedure Check_Reserved_Interrupt
(Interrupt
: Interrupt_ID
) is
285 if Is_Reserved
(Interrupt
) then
286 raise Program_Error
with
287 "Interrupt" & Interrupt_ID
'Image (Interrupt
) & " is reserved";
291 end Check_Reserved_Interrupt
;
293 ---------------------
294 -- Current_Handler --
295 ---------------------
297 function Current_Handler
298 (Interrupt
: Interrupt_ID
) return Parameterless_Handler
301 Check_Reserved_Interrupt
(Interrupt
);
303 -- ??? Since Parameterless_Handler is not Atomic, the
304 -- current implementation is wrong. We need a new service in
305 -- Interrupt_Manager to ensure atomicity.
307 return User_Handler
(Interrupt
).H
;
314 -- Calling this procedure with Static = True means we want to Detach the
315 -- current handler regardless of the previous handler's binding status
316 -- (i.e. do not care if it is a dynamic or static handler).
318 -- This option is needed so that during the finalization of a PO, we can
319 -- detach handlers attached through pragma Attach_Handler.
321 procedure Detach_Handler
322 (Interrupt
: Interrupt_ID
;
323 Static
: Boolean := False) is
325 Check_Reserved_Interrupt
(Interrupt
);
326 Interrupt_Manager
.Detach_Handler
(Interrupt
, Static
);
329 ------------------------------
330 -- Detach_Interrupt_Entries --
331 ------------------------------
333 procedure Detach_Interrupt_Entries
(T
: Task_Id
) is
335 Interrupt_Manager
.Detach_Interrupt_Entries
(T
);
336 end Detach_Interrupt_Entries
;
338 ----------------------
339 -- Exchange_Handler --
340 ----------------------
342 -- Calling this procedure with New_Handler = null and Static = True
343 -- means we want to detach the current handler regardless of the
344 -- previous handler's binding status (i.e. do not care if it is a
345 -- dynamic or static handler).
347 -- This option is needed so that during the finalization of a PO, we
348 -- can detach handlers attached through pragma Attach_Handler.
350 procedure Exchange_Handler
351 (Old_Handler
: out Parameterless_Handler
;
352 New_Handler
: Parameterless_Handler
;
353 Interrupt
: Interrupt_ID
;
354 Static
: Boolean := False)
357 Check_Reserved_Interrupt
(Interrupt
);
358 Interrupt_Manager
.Exchange_Handler
359 (Old_Handler
, New_Handler
, Interrupt
, Static
);
360 end Exchange_Handler
;
366 procedure Finalize
(Object
: in out Static_Interrupt_Protection
) is
368 -- ??? loop to be executed only when we're not doing library level
369 -- finalization, since in this case all interrupt / signal tasks are
372 if not Interrupt_Manager
'Terminated then
373 for N
in reverse Object
.Previous_Handlers
'Range loop
374 Interrupt_Manager
.Attach_Handler
375 (New_Handler
=> Object
.Previous_Handlers
(N
).Handler
,
376 Interrupt
=> Object
.Previous_Handlers
(N
).Interrupt
,
377 Static
=> Object
.Previous_Handlers
(N
).Static
,
378 Restoration
=> True);
382 Tasking
.Protected_Objects
.Entries
.Finalize
383 (Tasking
.Protected_Objects
.Entries
.Protection_Entries
(Object
));
386 --------------------------------
387 -- Finalize_Interrupt_Servers --
388 --------------------------------
390 -- Restore default handlers for interrupt servers
392 -- This is called by the Interrupt_Manager task when it receives the abort
393 -- signal during program finalization.
395 procedure Finalize_Interrupt_Servers
is
396 HW_Interrupts
: constant Boolean := HW_Interrupt
'Last >= 0;
399 if HW_Interrupts
then
400 for Int
in HW_Interrupt
loop
401 if Server_ID
(Interrupt_ID
(Int
)) /= null
403 not Ada
.Task_Identification
.Is_Terminated
404 (To_Ada
(Server_ID
(Interrupt_ID
(Int
))))
406 Interrupt_Manager
.Attach_Handler
407 (New_Handler
=> null,
408 Interrupt
=> Interrupt_ID
(Int
),
410 Restoration
=> True);
414 end Finalize_Interrupt_Servers
;
416 -------------------------------------
417 -- Has_Interrupt_Or_Attach_Handler --
418 -------------------------------------
420 function Has_Interrupt_Or_Attach_Handler
421 (Object
: access Dynamic_Interrupt_Protection
)
424 pragma Unreferenced
(Object
);
427 end Has_Interrupt_Or_Attach_Handler
;
429 function Has_Interrupt_Or_Attach_Handler
430 (Object
: access Static_Interrupt_Protection
)
433 pragma Unreferenced
(Object
);
436 end Has_Interrupt_Or_Attach_Handler
;
438 ----------------------
439 -- Ignore_Interrupt --
440 ----------------------
442 procedure Ignore_Interrupt
(Interrupt
: Interrupt_ID
) is
444 Unimplemented
("Ignore_Interrupt");
445 end Ignore_Interrupt
;
447 ----------------------
448 -- Install_Handlers --
449 ----------------------
451 procedure Install_Handlers
452 (Object
: access Static_Interrupt_Protection
;
453 New_Handlers
: New_Handler_Array
)
456 for N
in New_Handlers
'Range loop
458 -- We need a lock around this ???
460 Object
.Previous_Handlers
(N
).Interrupt
:= New_Handlers
(N
).Interrupt
;
461 Object
.Previous_Handlers
(N
).Static
:= User_Handler
462 (New_Handlers
(N
).Interrupt
).Static
;
464 -- We call Exchange_Handler and not directly Interrupt_Manager.
465 -- Exchange_Handler so we get the Is_Reserved check.
468 (Old_Handler
=> Object
.Previous_Handlers
(N
).Handler
,
469 New_Handler
=> New_Handlers
(N
).Handler
,
470 Interrupt
=> New_Handlers
(N
).Interrupt
,
473 end Install_Handlers
;
475 ---------------------------------
476 -- Install_Restricted_Handlers --
477 ---------------------------------
479 procedure Install_Restricted_Handlers
(Handlers
: New_Handler_Array
) is
481 for N
in Handlers
'Range loop
482 Attach_Handler
(Handlers
(N
).Handler
, Handlers
(N
).Interrupt
, True);
484 end Install_Restricted_Handlers
;
486 ------------------------------
487 -- Install_Umbrella_Handler --
488 ------------------------------
490 procedure Install_Umbrella_Handler
491 (Interrupt
: HW_Interrupt
;
492 Handler
: System
.OS_Interface
.Interrupt_Handler
)
494 Vec
: constant Interrupt_Vector
:=
495 Interrupt_Number_To_Vector
(int
(Interrupt
));
500 -- Only install umbrella handler when no Ada handler has already been
501 -- installed. Note that the interrupt number is passed as a parameter
502 -- when an interrupt occurs, so the umbrella handler has a different
503 -- wrapper generated by intConnect for each interrupt number.
505 if not Handler_Installed
(Interrupt
) then
507 Interrupt_Connect
(Vec
, Handler
, System
.Address
(Interrupt
));
508 pragma Assert
(Status
= 0);
510 Handler_Installed
(Interrupt
) := True;
512 end Install_Umbrella_Handler
;
518 function Is_Blocked
(Interrupt
: Interrupt_ID
) return Boolean is
520 Unimplemented
("Is_Blocked");
524 -----------------------
525 -- Is_Entry_Attached --
526 -----------------------
528 function Is_Entry_Attached
(Interrupt
: Interrupt_ID
) return Boolean is
530 Check_Reserved_Interrupt
(Interrupt
);
531 return User_Entry
(Interrupt
).T
/= Null_Task
;
532 end Is_Entry_Attached
;
534 -------------------------
535 -- Is_Handler_Attached --
536 -------------------------
538 function Is_Handler_Attached
(Interrupt
: Interrupt_ID
) return Boolean is
540 Check_Reserved_Interrupt
(Interrupt
);
541 return User_Handler
(Interrupt
).H
/= null;
542 end Is_Handler_Attached
;
548 function Is_Ignored
(Interrupt
: Interrupt_ID
) return Boolean is
550 Unimplemented
("Is_Ignored");
558 function Is_Registered
(Handler
: Parameterless_Handler
) return Boolean is
559 type Fat_Ptr
is record
560 Object_Addr
: System
.Address
;
561 Handler_Addr
: System
.Address
;
564 function To_Fat_Ptr
is new Ada
.Unchecked_Conversion
565 (Parameterless_Handler
, Fat_Ptr
);
571 if Handler
= null then
575 Fat
:= To_Fat_Ptr
(Handler
);
577 Ptr
:= Registered_Handler_Head
;
579 while Ptr
/= null loop
580 if Ptr
.H
= Fat
.Handler_Addr
then
594 function Is_Reserved
(Interrupt
: Interrupt_ID
) return Boolean is
595 use System
.Interrupt_Management
;
597 return Reserve
(System
.Interrupt_Management
.Interrupt_ID
(Interrupt
));
600 ----------------------
601 -- Notify_Interrupt --
602 ----------------------
604 -- Umbrella handler for vectored hardware interrupts (as opposed to
605 -- signals and exceptions). As opposed to the signal implementation,
606 -- this handler is installed in the vector table when the first Ada
607 -- handler is attached to the interrupt. However because VxWorks don't
608 -- support disconnecting handlers, this subprogram always test whether
609 -- or not an Ada handler is effectively attached.
611 -- Otherwise, the handler that existed prior to program startup is
612 -- in the vector table. This ensures that handlers installed by
613 -- the BSP are active unless explicitly replaced in the program text.
615 -- Each Interrupt_Server_Task has an associated binary semaphore
616 -- on which it pends once it's been started. This routine determines
617 -- The appropriate semaphore and issues a semGive call, waking
618 -- the server task. When a handler is unbound,
619 -- System.Interrupts.Unbind_Handler issues a Binary_Semaphore_Flush,
620 -- and the server task deletes its semaphore and terminates.
622 procedure Notify_Interrupt
(Param
: System
.Address
) is
623 Interrupt
: constant Interrupt_ID
:= Interrupt_ID
(Param
);
625 Id
: constant Binary_Semaphore_Id
:= Semaphore_ID_Map
(Interrupt
);
631 Status
:= Binary_Semaphore_Release
(Id
);
632 pragma Assert
(Status
= 0);
634 end Notify_Interrupt
;
640 function Reference
(Interrupt
: Interrupt_ID
) return System
.Address
is
642 Check_Reserved_Interrupt
(Interrupt
);
643 return Storage_Elements
.To_Address
644 (Storage_Elements
.Integer_Address
(Interrupt
));
647 --------------------------------
648 -- Register_Interrupt_Handler --
649 --------------------------------
651 procedure Register_Interrupt_Handler
(Handler_Addr
: System
.Address
) is
652 New_Node_Ptr
: R_Link
;
655 -- This routine registers a handler as usable for dynamic
656 -- interrupt handler association. Routines attaching and detaching
657 -- handlers dynamically should determine whether the handler is
658 -- registered. Program_Error should be raised if it is not registered.
660 -- Pragma Interrupt_Handler can only appear in a library
661 -- level PO definition and instantiation. Therefore, we do not need
662 -- to implement an unregister operation. Nor do we need to
663 -- protect the queue structure with a lock.
665 pragma Assert
(Handler_Addr
/= System
.Null_Address
);
667 New_Node_Ptr
:= new Registered_Handler
;
668 New_Node_Ptr
.H
:= Handler_Addr
;
670 if Registered_Handler_Head
= null then
671 Registered_Handler_Head
:= New_Node_Ptr
;
672 Registered_Handler_Tail
:= New_Node_Ptr
;
675 Registered_Handler_Tail
.Next
:= New_Node_Ptr
;
676 Registered_Handler_Tail
:= New_Node_Ptr
;
678 end Register_Interrupt_Handler
;
680 -----------------------
681 -- Unblock_Interrupt --
682 -----------------------
684 procedure Unblock_Interrupt
(Interrupt
: Interrupt_ID
) is
686 Unimplemented
("Unblock_Interrupt");
687 end Unblock_Interrupt
;
693 function Unblocked_By
694 (Interrupt
: Interrupt_ID
) return System
.Tasking
.Task_Id
697 Unimplemented
("Unblocked_By");
701 ------------------------
702 -- Unignore_Interrupt --
703 ------------------------
705 procedure Unignore_Interrupt
(Interrupt
: Interrupt_ID
) is
707 Unimplemented
("Unignore_Interrupt");
708 end Unignore_Interrupt
;
714 procedure Unimplemented
(Feature
: String) is
716 raise Program_Error
with Feature
& " not implemented on VxWorks";
719 -----------------------
720 -- Interrupt_Manager --
721 -----------------------
723 task body Interrupt_Manager
is
729 procedure Bind_Handler
(Interrupt
: Interrupt_ID
);
730 -- This procedure does not do anything if a signal is blocked.
731 -- Otherwise, we have to interrupt Server_Task for status change through
734 procedure Unbind_Handler
(Interrupt
: Interrupt_ID
);
735 -- This procedure does not do anything if a signal is blocked.
736 -- Otherwise, we have to interrupt Server_Task for status change
737 -- through an abort signal.
739 procedure Unprotected_Exchange_Handler
740 (Old_Handler
: out Parameterless_Handler
;
741 New_Handler
: Parameterless_Handler
;
742 Interrupt
: Interrupt_ID
;
744 Restoration
: Boolean := False);
746 procedure Unprotected_Detach_Handler
747 (Interrupt
: Interrupt_ID
;
754 procedure Bind_Handler
(Interrupt
: Interrupt_ID
) is
756 Install_Umbrella_Handler
757 (HW_Interrupt
(Interrupt
), Notify_Interrupt
'Access);
764 procedure Unbind_Handler
(Interrupt
: Interrupt_ID
) is
768 -- Flush server task off semaphore, allowing it to terminate
770 Status
:= Binary_Semaphore_Flush
(Semaphore_ID_Map
(Interrupt
));
771 pragma Assert
(Status
= 0);
774 --------------------------------
775 -- Unprotected_Detach_Handler --
776 --------------------------------
778 procedure Unprotected_Detach_Handler
779 (Interrupt
: Interrupt_ID
;
782 Old_Handler
: Parameterless_Handler
;
784 if User_Entry
(Interrupt
).T
/= Null_Task
then
785 -- If an interrupt entry is installed raise
786 -- Program_Error. (propagate it to the caller).
788 raise Program_Error
with
789 "An interrupt entry is already installed";
792 -- Note : Static = True will pass the following check. This is the
793 -- case when we want to detach a handler regardless of the static
794 -- status of the Current_Handler.
796 if not Static
and then User_Handler
(Interrupt
).Static
then
798 -- Trying to detach a static Interrupt Handler. raise
801 raise Program_Error
with
802 "Trying to detach a static Interrupt Handler";
805 Old_Handler
:= User_Handler
(Interrupt
).H
;
809 User_Handler
(Interrupt
).H
:= null;
810 User_Handler
(Interrupt
).Static
:= False;
812 if Old_Handler
/= null then
813 Unbind_Handler
(Interrupt
);
815 end Unprotected_Detach_Handler
;
817 ----------------------------------
818 -- Unprotected_Exchange_Handler --
819 ----------------------------------
821 procedure Unprotected_Exchange_Handler
822 (Old_Handler
: out Parameterless_Handler
;
823 New_Handler
: Parameterless_Handler
;
824 Interrupt
: Interrupt_ID
;
826 Restoration
: Boolean := False)
829 if User_Entry
(Interrupt
).T
/= Null_Task
then
831 -- If an interrupt entry is already installed, raise
832 -- Program_Error. (propagate it to the caller).
834 raise Program_Error
with "An interrupt is already installed";
837 -- Note : A null handler with Static = True will
838 -- pass the following check. This is the case when we want to
839 -- detach a handler regardless of the Static status
840 -- of Current_Handler.
841 -- We don't check anything if Restoration is True, since we
842 -- may be detaching a static handler to restore a dynamic one.
844 if not Restoration
and then not Static
845 and then (User_Handler
(Interrupt
).Static
847 -- Trying to overwrite a static Interrupt Handler with a
850 -- The new handler is not specified as an
851 -- Interrupt Handler by a pragma.
853 or else not Is_Registered
(New_Handler
))
855 raise Program_Error
with
856 "Trying to overwrite a static Interrupt Handler with a " &
860 -- Save the old handler
862 Old_Handler
:= User_Handler
(Interrupt
).H
;
866 User_Handler
(Interrupt
).H
:= New_Handler
;
868 if New_Handler
= null then
870 -- The null handler means we are detaching the handler
872 User_Handler
(Interrupt
).Static
:= False;
875 User_Handler
(Interrupt
).Static
:= Static
;
878 -- Invoke a corresponding Server_Task if not yet created.
879 -- Place Task_Id info in Server_ID array.
881 if New_Handler
/= null
883 (Server_ID
(Interrupt
) = Null_Task
885 Ada
.Task_Identification
.Is_Terminated
886 (To_Ada
(Server_ID
(Interrupt
))))
888 Interrupt_Access_Hold
:=
889 new Interrupt_Server_Task
(Interrupt
, Binary_Semaphore_Create
);
890 Server_ID
(Interrupt
) :=
891 To_System
(Interrupt_Access_Hold
.all'Identity);
894 if (New_Handler
= null) and then Old_Handler
/= null then
896 -- Restore default handler
898 Unbind_Handler
(Interrupt
);
900 elsif Old_Handler
= null then
902 -- Save default handler
904 Bind_Handler
(Interrupt
);
906 end Unprotected_Exchange_Handler
;
908 -- Start of processing for Interrupt_Manager
911 -- By making this task independent of any master, when the process
912 -- goes away, the Interrupt_Manager will terminate gracefully.
914 System
.Tasking
.Utilities
.Make_Independent
;
917 -- A block is needed to absorb Program_Error exception
920 Old_Handler
: Parameterless_Handler
;
924 accept Attach_Handler
925 (New_Handler
: Parameterless_Handler
;
926 Interrupt
: Interrupt_ID
;
928 Restoration
: Boolean := False)
930 Unprotected_Exchange_Handler
931 (Old_Handler
, New_Handler
, Interrupt
, Static
, Restoration
);
935 accept Exchange_Handler
936 (Old_Handler
: out Parameterless_Handler
;
937 New_Handler
: Parameterless_Handler
;
938 Interrupt
: Interrupt_ID
;
941 Unprotected_Exchange_Handler
942 (Old_Handler
, New_Handler
, Interrupt
, Static
);
943 end Exchange_Handler
;
946 accept Detach_Handler
947 (Interrupt
: Interrupt_ID
;
950 Unprotected_Detach_Handler
(Interrupt
, Static
);
953 accept Bind_Interrupt_To_Entry
955 E
: Task_Entry_Index
;
956 Interrupt
: Interrupt_ID
)
958 -- If there is a binding already (either a procedure or an
959 -- entry), raise Program_Error (propagate it to the caller).
961 if User_Handler
(Interrupt
).H
/= null
962 or else User_Entry
(Interrupt
).T
/= Null_Task
964 raise Program_Error
with
965 "A binding for this interrupt is already present";
968 User_Entry
(Interrupt
) := Entry_Assoc
'(T => T, E => E);
970 -- Indicate the attachment of interrupt entry in the ATCB.
971 -- This is needed so when an interrupt entry task terminates
972 -- the binding can be cleaned. The call to unbinding must be
973 -- make by the task before it terminates.
975 T.Interrupt_Entry := True;
977 -- Invoke a corresponding Server_Task if not yet created.
978 -- Place Task_Id info in Server_ID array.
980 if Server_ID (Interrupt) = Null_Task
982 Ada.Task_Identification.Is_Terminated
983 (To_Ada (Server_ID (Interrupt)))
985 Interrupt_Access_Hold := new Interrupt_Server_Task
986 (Interrupt, Binary_Semaphore_Create);
987 Server_ID (Interrupt) :=
988 To_System (Interrupt_Access_Hold.all'Identity);
991 Bind_Handler (Interrupt);
992 end Bind_Interrupt_To_Entry;
995 accept Detach_Interrupt_Entries (T : Task_Id) do
996 for Int in Interrupt_ID'Range loop
997 if not Is_Reserved (Int) then
998 if User_Entry (Int).T = T then
1001 (T
=> Null_Task
, E
=> Null_Task_Entry
);
1002 Unbind_Handler
(Int
);
1007 -- Indicate in ATCB that no interrupt entries are attached
1009 T
.Interrupt_Entry
:= False;
1010 end Detach_Interrupt_Entries
;
1014 -- If there is a Program_Error we just want to propagate it to
1015 -- the caller and do not want to stop this task.
1017 when Program_Error
=>
1021 pragma Assert
(False);
1027 when Standard
'Abort_Signal =>
1029 -- Flush interrupt server semaphores, so they can terminate
1031 Finalize_Interrupt_Servers
;
1033 end Interrupt_Manager
;
1035 ---------------------------
1036 -- Interrupt_Server_Task --
1037 ---------------------------
1039 -- Server task for vectored hardware interrupt handling
1041 task body Interrupt_Server_Task
is
1042 Self_Id
: constant Task_Id
:= Self
;
1043 Tmp_Handler
: Parameterless_Handler
;
1045 Tmp_Entry_Index
: Task_Entry_Index
;
1049 System
.Tasking
.Utilities
.Make_Independent
;
1050 Semaphore_ID_Map
(Interrupt
) := Int_Sema
;
1053 -- Pend on semaphore that will be triggered by the
1054 -- umbrella handler when the associated interrupt comes in
1056 Status
:= Binary_Semaphore_Obtain
(Int_Sema
);
1057 pragma Assert
(Status
= 0);
1059 if User_Handler
(Interrupt
).H
/= null then
1061 -- Protected procedure handler
1063 Tmp_Handler
:= User_Handler
(Interrupt
).H
;
1066 elsif User_Entry
(Interrupt
).T
/= Null_Task
then
1068 -- Interrupt entry handler
1070 Tmp_ID
:= User_Entry
(Interrupt
).T
;
1071 Tmp_Entry_Index
:= User_Entry
(Interrupt
).E
;
1072 System
.Tasking
.Rendezvous
.Call_Simple
1073 (Tmp_ID
, Tmp_Entry_Index
, System
.Null_Address
);
1076 -- Semaphore has been flushed by an unbind operation in
1077 -- the Interrupt_Manager. Terminate the server task.
1079 -- Wait for the Interrupt_Manager to complete its work
1081 POP
.Write_Lock
(Self_Id
);
1083 -- Unassociate the interrupt handler
1085 Semaphore_ID_Map
(Interrupt
) := 0;
1087 -- Delete the associated semaphore
1089 Status
:= Binary_Semaphore_Delete
(Int_Sema
);
1091 pragma Assert
(Status
= 0);
1093 -- Set status for the Interrupt_Manager
1095 Server_ID
(Interrupt
) := Null_Task
;
1096 POP
.Unlock
(Self_Id
);
1101 end Interrupt_Server_Task
;
1104 -- Get Interrupt_Manager's ID so that Abort_Interrupt can be sent
1106 Interrupt_Manager_ID
:= To_System
(Interrupt_Manager
'Identity);
1107 end System
.Interrupts
;