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) 1998-2009, 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 ------------------------------------------------------------------------------
32 -- This is the IRIX & NT version of this package
34 with Ada
.Task_Identification
;
35 with Ada
.Unchecked_Conversion
;
39 with System
.Storage_Elements
;
40 with System
.Task_Primitives
.Operations
;
41 with System
.Tasking
.Utilities
;
42 with System
.Tasking
.Rendezvous
;
43 with System
.Tasking
.Initialization
;
44 with System
.Interrupt_Management
;
45 with System
.Parameters
;
47 package body System
.Interrupts
is
51 use System
.OS_Interface
;
54 package STPO
renames System
.Task_Primitives
.Operations
;
55 package IMNG
renames System
.Interrupt_Management
;
57 subtype int
is Interfaces
.C
.int
;
59 function To_System
is new Ada
.Unchecked_Conversion
60 (Ada
.Task_Identification
.Task_Id
, Task_Id
);
62 type Handler_Kind
is (Unknown
, Task_Entry
, Protected_Procedure
);
64 type Handler_Desc
is record
65 Kind
: Handler_Kind
:= Unknown
;
68 H
: Parameterless_Handler
;
69 Static
: Boolean := False;
72 task type Server_Task
(Interrupt
: Interrupt_ID
) is
73 pragma Interrupt_Priority
(System
.Interrupt_Priority
'Last);
76 type Server_Task_Access
is access Server_Task
;
78 Handlers
: array (Interrupt_ID
) of Task_Id
;
79 Descriptors
: array (Interrupt_ID
) of Handler_Desc
;
80 Interrupt_Count
: array (Interrupt_ID
) of Integer := (others => 0);
82 pragma Volatile_Components
(Interrupt_Count
);
84 procedure Attach_Handler
85 (New_Handler
: Parameterless_Handler
;
86 Interrupt
: Interrupt_ID
;
88 Restoration
: Boolean);
89 -- This internal procedure is needed to finalize protected objects
90 -- that contain interrupt handlers.
92 procedure Signal_Handler
(Sig
: Interrupt_ID
);
93 pragma Convention
(C
, Signal_Handler
);
94 -- This procedure is used to handle all the signals
96 -- Type and Head, Tail of the list containing Registered Interrupt
97 -- Handlers. These definitions are used to register the handlers
98 -- specified by the pragma Interrupt_Handler.
100 --------------------------
101 -- Handler Registration --
102 --------------------------
104 type Registered_Handler
;
105 type R_Link
is access all Registered_Handler
;
107 type Registered_Handler
is record
108 H
: System
.Address
:= System
.Null_Address
;
109 Next
: R_Link
:= null;
112 Registered_Handlers
: R_Link
:= null;
114 function Is_Registered
(Handler
: Parameterless_Handler
) return Boolean;
115 -- See if the Handler has been "pragma"ed using Interrupt_Handler.
116 -- Always consider a null handler as registered.
118 type Handler_Ptr
is access procedure (Sig
: Interrupt_ID
);
119 pragma Convention
(C
, Handler_Ptr
);
121 function TISR
is new Ada
.Unchecked_Conversion
(Handler_Ptr
, isr_address
);
127 procedure Signal_Handler
(Sig
: Interrupt_ID
) is
128 Handler
: Task_Id
renames Handlers
(Sig
);
131 if Intr_Attach_Reset
and then
132 intr_attach
(int
(Sig
), TISR
(Signal_Handler
'Access)) = FUNC_ERR
137 if Handler
/= null then
138 Interrupt_Count
(Sig
) := Interrupt_Count
(Sig
) + 1;
139 STPO
.Wakeup
(Handler
, Interrupt_Server_Idle_Sleep
);
147 function Is_Reserved
(Interrupt
: Interrupt_ID
) return Boolean is
149 return IMNG
.Reserve
(IMNG
.Interrupt_ID
(Interrupt
));
152 -----------------------
153 -- Is_Entry_Attached --
154 -----------------------
156 function Is_Entry_Attached
(Interrupt
: Interrupt_ID
) return Boolean is
158 if Is_Reserved
(Interrupt
) then
159 raise Program_Error
with
160 "Interrupt" & Interrupt_ID
'Image (Interrupt
) & " is reserved";
163 return Descriptors
(Interrupt
).T
/= Null_Task
;
164 end Is_Entry_Attached
;
166 -------------------------
167 -- Is_Handler_Attached --
168 -------------------------
170 function Is_Handler_Attached
(Interrupt
: Interrupt_ID
) return Boolean is
172 if Is_Reserved
(Interrupt
) then
173 raise Program_Error
with
174 "Interrupt" & Interrupt_ID
'Image (Interrupt
) & " is reserved";
176 return Descriptors
(Interrupt
).Kind
/= Unknown
;
178 end Is_Handler_Attached
;
184 function Is_Ignored
(Interrupt
: Interrupt_ID
) return Boolean is
194 function Unblocked_By
(Interrupt
: Interrupt_ID
) return Task_Id
is
200 ----------------------
201 -- Ignore_Interrupt --
202 ----------------------
204 procedure Ignore_Interrupt
(Interrupt
: Interrupt_ID
) is
207 end Ignore_Interrupt
;
209 ------------------------
210 -- Unignore_Interrupt --
211 ------------------------
213 procedure Unignore_Interrupt
(Interrupt
: Interrupt_ID
) is
216 end Unignore_Interrupt
;
218 -------------------------------------
219 -- Has_Interrupt_Or_Attach_Handler --
220 -------------------------------------
222 function Has_Interrupt_Or_Attach_Handler
223 (Object
: access Dynamic_Interrupt_Protection
) return Boolean
225 pragma Unreferenced
(Object
);
228 end Has_Interrupt_Or_Attach_Handler
;
234 procedure Finalize
(Object
: in out Static_Interrupt_Protection
) is
236 -- ??? loop to be executed only when we're not doing library level
237 -- finalization, since in this case all interrupt tasks are gone.
239 for N
in reverse Object
.Previous_Handlers
'Range loop
241 (New_Handler
=> Object
.Previous_Handlers
(N
).Handler
,
242 Interrupt
=> Object
.Previous_Handlers
(N
).Interrupt
,
243 Static
=> Object
.Previous_Handlers
(N
).Static
,
244 Restoration
=> True);
247 Tasking
.Protected_Objects
.Entries
.Finalize
248 (Tasking
.Protected_Objects
.Entries
.Protection_Entries
(Object
));
251 -------------------------------------
252 -- Has_Interrupt_Or_Attach_Handler --
253 -------------------------------------
255 function Has_Interrupt_Or_Attach_Handler
256 (Object
: access Static_Interrupt_Protection
) return Boolean
258 pragma Unreferenced
(Object
);
261 end Has_Interrupt_Or_Attach_Handler
;
263 ----------------------
264 -- Install_Handlers --
265 ----------------------
267 procedure Install_Handlers
268 (Object
: access Static_Interrupt_Protection
;
269 New_Handlers
: New_Handler_Array
)
272 for N
in New_Handlers
'Range loop
274 -- We need a lock around this ???
276 Object
.Previous_Handlers
(N
).Interrupt
:= New_Handlers
(N
).Interrupt
;
277 Object
.Previous_Handlers
(N
).Static
:= Descriptors
278 (New_Handlers
(N
).Interrupt
).Static
;
280 -- We call Exchange_Handler and not directly Interrupt_Manager.
281 -- Exchange_Handler so we get the Is_Reserved check.
284 (Old_Handler
=> Object
.Previous_Handlers
(N
).Handler
,
285 New_Handler
=> New_Handlers
(N
).Handler
,
286 Interrupt
=> New_Handlers
(N
).Interrupt
,
289 end Install_Handlers
;
291 ---------------------------------
292 -- Install_Restricted_Handlers --
293 ---------------------------------
295 procedure Install_Restricted_Handlers
(Handlers
: New_Handler_Array
) is
297 for N
in Handlers
'Range loop
298 Attach_Handler
(Handlers
(N
).Handler
, Handlers
(N
).Interrupt
, True);
300 end Install_Restricted_Handlers
;
302 ---------------------
303 -- Current_Handler --
304 ---------------------
306 function Current_Handler
307 (Interrupt
: Interrupt_ID
) return Parameterless_Handler
310 if Is_Reserved
(Interrupt
) then
314 if Descriptors
(Interrupt
).Kind
= Protected_Procedure
then
315 return Descriptors
(Interrupt
).H
;
325 procedure Attach_Handler
326 (New_Handler
: Parameterless_Handler
;
327 Interrupt
: Interrupt_ID
;
328 Static
: Boolean := False) is
330 Attach_Handler
(New_Handler
, Interrupt
, Static
, False);
333 procedure Attach_Handler
334 (New_Handler
: Parameterless_Handler
;
335 Interrupt
: Interrupt_ID
;
337 Restoration
: Boolean)
339 New_Task
: Server_Task_Access
;
342 if Is_Reserved
(Interrupt
) then
346 if not Restoration
and then not Static
348 -- Tries to overwrite a static Interrupt Handler with dynamic handle
351 (Descriptors
(Interrupt
).Static
353 -- New handler not specified as an Interrupt Handler by a pragma
355 or else not Is_Registered
(New_Handler
))
357 raise Program_Error
with
358 "Trying to overwrite a static Interrupt Handler with a " &
362 if Handlers
(Interrupt
) = null then
363 New_Task
:= new Server_Task
(Interrupt
);
364 Handlers
(Interrupt
) := To_System
(New_Task
.all'Identity);
367 if intr_attach
(int
(Interrupt
),
368 TISR
(Signal_Handler
'Access)) = FUNC_ERR
373 if New_Handler
= null then
375 -- The null handler means we are detaching the handler
377 Descriptors
(Interrupt
) :=
378 (Kind
=> Unknown
, T
=> null, E
=> 0, H
=> null, Static
=> False);
381 Descriptors
(Interrupt
).Kind
:= Protected_Procedure
;
382 Descriptors
(Interrupt
).H
:= New_Handler
;
383 Descriptors
(Interrupt
).Static
:= Static
;
387 ----------------------
388 -- Exchange_Handler --
389 ----------------------
391 procedure Exchange_Handler
392 (Old_Handler
: out Parameterless_Handler
;
393 New_Handler
: Parameterless_Handler
;
394 Interrupt
: Interrupt_ID
;
395 Static
: Boolean := False)
398 if Is_Reserved
(Interrupt
) then
402 if Descriptors
(Interrupt
).Kind
= Task_Entry
then
404 -- In case we have an Interrupt Entry already installed.
405 -- raise a program error. (propagate it to the caller).
407 raise Program_Error
with "An interrupt is already installed";
410 Old_Handler
:= Current_Handler
(Interrupt
);
411 Attach_Handler
(New_Handler
, Interrupt
, Static
);
413 end Exchange_Handler
;
419 procedure Detach_Handler
420 (Interrupt
: Interrupt_ID
;
421 Static
: Boolean := False)
424 if Is_Reserved
(Interrupt
) then
428 if Descriptors
(Interrupt
).Kind
= Task_Entry
then
429 raise Program_Error
with "Trying to detach an Interrupt Entry";
432 if not Static
and then Descriptors
(Interrupt
).Static
then
433 raise Program_Error
with
434 "Trying to detach a static Interrupt Handler";
437 Descriptors
(Interrupt
) :=
438 (Kind
=> Unknown
, T
=> null, E
=> 0, H
=> null, Static
=> False);
440 if intr_attach
(int
(Interrupt
), null) = FUNC_ERR
then
449 function Reference
(Interrupt
: Interrupt_ID
) return System
.Address
is
450 Signal
: constant System
.Address
:=
451 System
.Storage_Elements
.To_Address
452 (System
.Storage_Elements
.Integer_Address
(Interrupt
));
455 if Is_Reserved
(Interrupt
) then
457 -- Only usable Interrupts can be used for binding it to an Entry
465 --------------------------------
466 -- Register_Interrupt_Handler --
467 --------------------------------
469 procedure Register_Interrupt_Handler
(Handler_Addr
: System
.Address
) is
471 Registered_Handlers
:=
472 new Registered_Handler
'(H => Handler_Addr, Next => Registered_Handlers);
473 end Register_Interrupt_Handler;
479 -- See if the Handler has been "pragma"ed using Interrupt_Handler.
480 -- Always consider a null handler as registered.
482 function Is_Registered (Handler : Parameterless_Handler) return Boolean is
483 Ptr : R_Link := Registered_Handlers;
485 type Fat_Ptr is record
486 Object_Addr : System.Address;
487 Handler_Addr : System.Address;
490 function To_Fat_Ptr is new Ada.Unchecked_Conversion
491 (Parameterless_Handler, Fat_Ptr);
496 if Handler = null then
500 Fat := To_Fat_Ptr (Handler);
502 while Ptr /= null loop
504 if Ptr.H = Fat.Handler_Addr then
514 -----------------------------
515 -- Bind_Interrupt_To_Entry --
516 -----------------------------
518 procedure Bind_Interrupt_To_Entry
520 E : Task_Entry_Index;
521 Int_Ref : System.Address)
523 Interrupt : constant Interrupt_ID :=
524 Interrupt_ID (Storage_Elements.To_Integer (Int_Ref));
526 New_Task : Server_Task_Access;
529 if Is_Reserved (Interrupt) then
533 if Descriptors (Interrupt).Kind /= Unknown then
534 raise Program_Error with
535 "A binding for this interrupt is already present";
538 if Handlers (Interrupt) = null then
539 New_Task := new Server_Task (Interrupt);
540 Handlers (Interrupt) := To_System (New_Task.all'Identity);
543 if intr_attach (int (Interrupt),
544 TISR (Signal_Handler'Access)) = FUNC_ERR
549 Descriptors (Interrupt).Kind := Task_Entry;
550 Descriptors (Interrupt).T := T;
551 Descriptors (Interrupt).E := E;
553 -- Indicate the attachment of Interrupt Entry in ATCB. This is needed so
554 -- that when an Interrupt Entry task terminates the binding can be
555 -- cleaned up. The call to unbinding must be make by the task before it
558 T.Interrupt_Entry := True;
559 end Bind_Interrupt_To_Entry;
561 ------------------------------
562 -- Detach_Interrupt_Entries --
563 ------------------------------
565 procedure Detach_Interrupt_Entries (T : Task_Id) is
567 for J in Interrupt_ID loop
568 if not Is_Reserved (J) then
569 if Descriptors (J).Kind = Task_Entry
570 and then Descriptors (J).T = T
572 Descriptors (J).Kind := Unknown;
574 if intr_attach (int (J), null) = FUNC_ERR then
581 -- Indicate in ATCB that no Interrupt Entries are attached
583 T.Interrupt_Entry := True;
584 end Detach_Interrupt_Entries;
586 ---------------------
587 -- Block_Interrupt --
588 ---------------------
590 procedure Block_Interrupt (Interrupt : Interrupt_ID) is
595 -----------------------
596 -- Unblock_Interrupt --
597 -----------------------
599 procedure Unblock_Interrupt (Interrupt : Interrupt_ID) is
602 end Unblock_Interrupt;
608 function Is_Blocked (Interrupt : Interrupt_ID) return Boolean is
614 task body Server_Task is
615 Desc : Handler_Desc renames Descriptors (Interrupt);
616 Self_Id : constant Task_Id := STPO.Self;
617 Temp : Parameterless_Handler;
620 Utilities.Make_Independent;
623 while Interrupt_Count (Interrupt) > 0 loop
624 Interrupt_Count (Interrupt) := Interrupt_Count (Interrupt) - 1;
630 Rendezvous.Call_Simple (Desc.T, Desc.E, Null_Address);
631 when Protected_Procedure =>
640 Initialization.Defer_Abort (Self_Id);
646 STPO.Write_Lock (Self_Id);
647 Self_Id.Common.State := Interrupt_Server_Idle_Sleep;
648 STPO.Sleep (Self_Id, Interrupt_Server_Idle_Sleep);
649 Self_Id.Common.State := Runnable;
650 STPO.Unlock (Self_Id);
656 Initialization.Undefer_Abort (Self_Id);
658 -- Undefer abort here to allow a window for this task to be aborted
659 -- at the time of system shutdown.
664 end System.Interrupts;