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-2005 Free Software Fundation --
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. --
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. --
29 -- GNARL was developed by the GNARL team at Florida State University. --
30 -- Extensive contributions were provided by Ada Core Technologies, Inc. --
32 ------------------------------------------------------------------------------
34 -- This is the IRIX & NT version of this package
36 with Ada
.Task_Identification
;
40 -- used for Raise_Exception
42 with System
.OS_Interface
;
43 -- used for intr_attach
45 with System
.Storage_Elements
;
46 -- used for To_Address
49 with System
.Task_Primitives
.Operations
;
56 with System
.Tasking
.Utilities
;
57 -- used for Make_Independent
59 with System
.Tasking
.Rendezvous
;
60 -- used for Call_Simple
62 with System
.Tasking
.Initialization
;
63 -- used for Defer_Abort
66 with System
.Interrupt_Management
;
68 with System
.Parameters
;
69 -- used for Single_Lock
74 with Unchecked_Conversion
;
76 package body System
.Interrupts
is
81 use System
.OS_Interface
;
84 package STPO
renames System
.Task_Primitives
.Operations
;
85 package IMNG
renames System
.Interrupt_Management
;
87 subtype int
is Interfaces
.C
.int
;
89 function To_System
is new Unchecked_Conversion
90 (Ada
.Task_Identification
.Task_Id
, Task_Id
);
92 type Handler_Kind
is (Unknown
, Task_Entry
, Protected_Procedure
);
94 type Handler_Desc
is record
95 Kind
: Handler_Kind
:= Unknown
;
98 H
: Parameterless_Handler
;
99 Static
: Boolean := False;
102 task type Server_Task
(Interrupt
: Interrupt_ID
) is
103 pragma Interrupt_Priority
(System
.Interrupt_Priority
'Last);
106 type Server_Task_Access
is access Server_Task
;
108 Handlers
: array (Interrupt_ID
) of Task_Id
;
109 Descriptors
: array (Interrupt_ID
) of Handler_Desc
;
110 Interrupt_Count
: array (Interrupt_ID
) of Integer := (others => 0);
112 pragma Volatile_Components
(Interrupt_Count
);
114 procedure Attach_Handler
115 (New_Handler
: Parameterless_Handler
;
116 Interrupt
: Interrupt_ID
;
118 Restoration
: Boolean);
119 -- This internal procedure is needed to finalize protected objects
120 -- that contain interrupt handlers.
122 procedure Signal_Handler
(Sig
: Interrupt_ID
);
123 -- This procedure is used to handle all the signals
125 -- Type and Head, Tail of the list containing Registered Interrupt
126 -- Handlers. These definitions are used to register the handlers
127 -- specified by the pragma Interrupt_Handler.
129 --------------------------
130 -- Handler Registration --
131 --------------------------
133 type Registered_Handler
;
134 type R_Link
is access all Registered_Handler
;
136 type Registered_Handler
is record
137 H
: System
.Address
:= System
.Null_Address
;
138 Next
: R_Link
:= null;
141 Registered_Handlers
: R_Link
:= null;
143 function Is_Registered
(Handler
: Parameterless_Handler
) return Boolean;
144 -- See if the Handler has been "pragma"ed using Interrupt_Handler.
145 -- Always consider a null handler as registered.
147 type Handler_Ptr
is access procedure (Sig
: Interrupt_ID
);
149 function TISR
is new Unchecked_Conversion
(Handler_Ptr
, isr_address
);
155 procedure Signal_Handler
(Sig
: Interrupt_ID
) is
156 Handler
: Task_Id
renames Handlers
(Sig
);
159 if Intr_Attach_Reset
and then
160 intr_attach
(int
(Sig
), TISR
(Signal_Handler
'Access)) = FUNC_ERR
165 if Handler
/= null then
166 Interrupt_Count
(Sig
) := Interrupt_Count
(Sig
) + 1;
167 STPO
.Wakeup
(Handler
, Interrupt_Server_Idle_Sleep
);
175 function Is_Reserved
(Interrupt
: Interrupt_ID
) return Boolean is
177 return IMNG
.Reserve
(IMNG
.Interrupt_ID
(Interrupt
));
180 -----------------------
181 -- Is_Entry_Attached --
182 -----------------------
184 function Is_Entry_Attached
(Interrupt
: Interrupt_ID
) return Boolean is
186 if Is_Reserved
(Interrupt
) then
187 Raise_Exception
(Program_Error
'Identity, "Interrupt" &
188 Interrupt_ID
'Image (Interrupt
) & " is reserved");
191 return Descriptors
(Interrupt
).T
/= Null_Task
;
192 end Is_Entry_Attached
;
194 -------------------------
195 -- Is_Handler_Attached --
196 -------------------------
198 function Is_Handler_Attached
(Interrupt
: Interrupt_ID
) return Boolean is
200 if Is_Reserved
(Interrupt
) then
201 Raise_Exception
(Program_Error
'Identity, "Interrupt" &
202 Interrupt_ID
'Image (Interrupt
) & " is reserved");
205 return Descriptors
(Interrupt
).Kind
/= Unknown
;
206 end Is_Handler_Attached
;
212 function Is_Ignored
(Interrupt
: Interrupt_ID
) return Boolean is
222 function Unblocked_By
(Interrupt
: Interrupt_ID
) return Task_Id
is
228 ----------------------
229 -- Ignore_Interrupt --
230 ----------------------
232 procedure Ignore_Interrupt
(Interrupt
: Interrupt_ID
) is
235 end Ignore_Interrupt
;
237 ------------------------
238 -- Unignore_Interrupt --
239 ------------------------
241 procedure Unignore_Interrupt
(Interrupt
: Interrupt_ID
) is
244 end Unignore_Interrupt
;
246 -------------------------------------
247 -- Has_Interrupt_Or_Attach_Handler --
248 -------------------------------------
250 function Has_Interrupt_Or_Attach_Handler
251 (Object
: access Dynamic_Interrupt_Protection
) return Boolean
253 pragma Unreferenced
(Object
);
256 end Has_Interrupt_Or_Attach_Handler
;
262 procedure Finalize
(Object
: in out Static_Interrupt_Protection
) is
264 -- ??? loop to be executed only when we're not doing library level
265 -- finalization, since in this case all interrupt tasks are gone.
267 for N
in reverse Object
.Previous_Handlers
'Range loop
269 (New_Handler
=> Object
.Previous_Handlers
(N
).Handler
,
270 Interrupt
=> Object
.Previous_Handlers
(N
).Interrupt
,
271 Static
=> Object
.Previous_Handlers
(N
).Static
,
272 Restoration
=> True);
275 Tasking
.Protected_Objects
.Entries
.Finalize
276 (Tasking
.Protected_Objects
.Entries
.Protection_Entries
(Object
));
279 -------------------------------------
280 -- Has_Interrupt_Or_Attach_Handler --
281 -------------------------------------
283 function Has_Interrupt_Or_Attach_Handler
284 (Object
: access Static_Interrupt_Protection
) return Boolean
286 pragma Unreferenced
(Object
);
289 end Has_Interrupt_Or_Attach_Handler
;
291 ----------------------
292 -- Install_Handlers --
293 ----------------------
295 procedure Install_Handlers
296 (Object
: access Static_Interrupt_Protection
;
297 New_Handlers
: New_Handler_Array
)
300 for N
in New_Handlers
'Range loop
302 -- We need a lock around this ???
304 Object
.Previous_Handlers
(N
).Interrupt
:= New_Handlers
(N
).Interrupt
;
305 Object
.Previous_Handlers
(N
).Static
:= Descriptors
306 (New_Handlers
(N
).Interrupt
).Static
;
308 -- We call Exchange_Handler and not directly Interrupt_Manager.
309 -- Exchange_Handler so we get the Is_Reserved check.
312 (Old_Handler
=> Object
.Previous_Handlers
(N
).Handler
,
313 New_Handler
=> New_Handlers
(N
).Handler
,
314 Interrupt
=> New_Handlers
(N
).Interrupt
,
317 end Install_Handlers
;
319 ---------------------
320 -- Current_Handler --
321 ---------------------
323 function Current_Handler
324 (Interrupt
: Interrupt_ID
) return Parameterless_Handler
327 if Is_Reserved
(Interrupt
) then
331 if Descriptors
(Interrupt
).Kind
= Protected_Procedure
then
332 return Descriptors
(Interrupt
).H
;
342 procedure Attach_Handler
343 (New_Handler
: Parameterless_Handler
;
344 Interrupt
: Interrupt_ID
;
345 Static
: Boolean := False) is
347 Attach_Handler
(New_Handler
, Interrupt
, Static
, False);
350 procedure Attach_Handler
351 (New_Handler
: Parameterless_Handler
;
352 Interrupt
: Interrupt_ID
;
354 Restoration
: Boolean)
356 New_Task
: Server_Task_Access
;
359 if Is_Reserved
(Interrupt
) then
363 if not Restoration
and then not Static
365 -- Tries to overwrite a static Interrupt Handler with dynamic handle
368 (Descriptors
(Interrupt
).Static
370 -- New handler not specified as an Interrupt Handler by a pragma
372 or else not Is_Registered
(New_Handler
))
374 Raise_Exception
(Program_Error
'Identity,
375 "Trying to overwrite a static Interrupt Handler with a " &
379 if Handlers
(Interrupt
) = null then
380 New_Task
:= new Server_Task
(Interrupt
);
381 Handlers
(Interrupt
) := To_System
(New_Task
.all'Identity);
384 if intr_attach
(int
(Interrupt
),
385 TISR
(Signal_Handler
'Access)) = FUNC_ERR
390 if New_Handler
= null then
392 -- The null handler means we are detaching the handler
394 Descriptors
(Interrupt
) :=
395 (Kind
=> Unknown
, T
=> null, E
=> 0, H
=> null, Static
=> False);
398 Descriptors
(Interrupt
).Kind
:= Protected_Procedure
;
399 Descriptors
(Interrupt
).H
:= New_Handler
;
400 Descriptors
(Interrupt
).Static
:= Static
;
404 ----------------------
405 -- Exchange_Handler --
406 ----------------------
408 procedure Exchange_Handler
409 (Old_Handler
: out Parameterless_Handler
;
410 New_Handler
: Parameterless_Handler
;
411 Interrupt
: Interrupt_ID
;
412 Static
: Boolean := False)
415 if Is_Reserved
(Interrupt
) then
419 if Descriptors
(Interrupt
).Kind
= Task_Entry
then
421 -- In case we have an Interrupt Entry already installed.
422 -- raise a program error. (propagate it to the caller).
424 Raise_Exception
(Program_Error
'Identity,
425 "An interrupt is already installed");
428 Old_Handler
:= Current_Handler
(Interrupt
);
429 Attach_Handler
(New_Handler
, Interrupt
, Static
);
430 end Exchange_Handler
;
436 procedure Detach_Handler
437 (Interrupt
: Interrupt_ID
;
438 Static
: Boolean := False)
441 if Is_Reserved
(Interrupt
) then
445 if Descriptors
(Interrupt
).Kind
= Task_Entry
then
446 Raise_Exception
(Program_Error
'Identity,
447 "Trying to detach an Interrupt Entry");
450 if not Static
and then Descriptors
(Interrupt
).Static
then
451 Raise_Exception
(Program_Error
'Identity,
452 "Trying to detach a static Interrupt Handler");
455 Descriptors
(Interrupt
) :=
456 (Kind
=> Unknown
, T
=> null, E
=> 0, H
=> null, Static
=> False);
458 if intr_attach
(int
(Interrupt
), null) = FUNC_ERR
then
467 function Reference
(Interrupt
: Interrupt_ID
) return System
.Address
is
468 Signal
: constant System
.Address
:=
469 System
.Storage_Elements
.To_Address
470 (System
.Storage_Elements
.Integer_Address
(Interrupt
));
473 if Is_Reserved
(Interrupt
) then
475 -- Only usable Interrupts can be used for binding it to an Entry
483 --------------------------------
484 -- Register_Interrupt_Handler --
485 --------------------------------
487 procedure Register_Interrupt_Handler
(Handler_Addr
: System
.Address
) is
489 Registered_Handlers
:=
490 new Registered_Handler
'(H => Handler_Addr, Next => Registered_Handlers);
491 end Register_Interrupt_Handler;
497 -- See if the Handler has been "pragma"ed using Interrupt_Handler.
498 -- Always consider a null handler as registered.
500 function Is_Registered (Handler : Parameterless_Handler) return Boolean is
501 Ptr : R_Link := Registered_Handlers;
503 type Fat_Ptr is record
504 Object_Addr : System.Address;
505 Handler_Addr : System.Address;
508 function To_Fat_Ptr is new Unchecked_Conversion
509 (Parameterless_Handler, Fat_Ptr);
514 if Handler = null then
518 Fat := To_Fat_Ptr (Handler);
520 while Ptr /= null loop
522 if Ptr.H = Fat.Handler_Addr then
532 -----------------------------
533 -- Bind_Interrupt_To_Entry --
534 -----------------------------
536 procedure Bind_Interrupt_To_Entry
538 E : Task_Entry_Index;
539 Int_Ref : System.Address)
541 Interrupt : constant Interrupt_ID :=
542 Interrupt_ID (Storage_Elements.To_Integer (Int_Ref));
544 New_Task : Server_Task_Access;
547 if Is_Reserved (Interrupt) then
551 if Descriptors (Interrupt).Kind /= Unknown then
552 Raise_Exception (Program_Error'Identity,
553 "A binding for this interrupt is already present");
556 if Handlers (Interrupt) = null then
557 New_Task := new Server_Task (Interrupt);
558 Handlers (Interrupt) := To_System (New_Task.all'Identity);
561 if intr_attach (int (Interrupt),
562 TISR (Signal_Handler'Access)) = FUNC_ERR
567 Descriptors (Interrupt).Kind := Task_Entry;
568 Descriptors (Interrupt).T := T;
569 Descriptors (Interrupt).E := E;
571 -- Indicate the attachment of Interrupt Entry in ATCB. This is needed so
572 -- that when an Interrupt Entry task terminates the binding can be
573 -- cleaned up. The call to unbinding must be make by the task before it
576 T.Interrupt_Entry := True;
577 end Bind_Interrupt_To_Entry;
579 ------------------------------
580 -- Detach_Interrupt_Entries --
581 ------------------------------
583 procedure Detach_Interrupt_Entries (T : Task_Id) is
585 for J in Interrupt_ID loop
586 if not Is_Reserved (J) then
587 if Descriptors (J).Kind = Task_Entry
588 and then Descriptors (J).T = T
590 Descriptors (J).Kind := Unknown;
592 if intr_attach (int (J), null) = FUNC_ERR then
599 -- Indicate in ATCB that no Interrupt Entries are attached
601 T.Interrupt_Entry := True;
602 end Detach_Interrupt_Entries;
604 ---------------------
605 -- Block_Interrupt --
606 ---------------------
608 procedure Block_Interrupt (Interrupt : Interrupt_ID) is
613 -----------------------
614 -- Unblock_Interrupt --
615 -----------------------
617 procedure Unblock_Interrupt (Interrupt : Interrupt_ID) is
620 end Unblock_Interrupt;
626 function Is_Blocked (Interrupt : Interrupt_ID) return Boolean is
632 task body Server_Task is
633 Desc : Handler_Desc renames Descriptors (Interrupt);
634 Self_Id : constant Task_Id := STPO.Self;
635 Temp : Parameterless_Handler;
638 Utilities.Make_Independent;
641 while Interrupt_Count (Interrupt) > 0 loop
642 Interrupt_Count (Interrupt) := Interrupt_Count (Interrupt) - 1;
648 Rendezvous.Call_Simple (Desc.T, Desc.E, Null_Address);
649 when Protected_Procedure =>
658 Initialization.Defer_Abort (Self_Id);
664 STPO.Write_Lock (Self_Id);
665 Self_Id.Common.State := Interrupt_Server_Idle_Sleep;
666 STPO.Sleep (Self_Id, Interrupt_Server_Idle_Sleep);
667 Self_Id.Common.State := Runnable;
668 STPO.Unlock (Self_Id);
674 Initialization.Undefer_Abort (Self_Id);
676 -- Undefer abort here to allow a window for this task to be aborted
677 -- at the time of system shutdown.
682 end System.Interrupts;