1 ------------------------------------------------------------------------------
3 -- GNU ADA RUN-TIME LIBRARY (GNARL) COMPONENTS --
5 -- S Y S T E M . T A S K _ P R I M I T I V E S .O P E R A T I O N S --
9 -- Copyright (C) 1992-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 package contains all the GNULL primitives that interface directly with
35 with System
.Parameters
;
37 with System
.OS_Interface
;
39 package System
.Task_Primitives
.Operations
is
42 package ST
renames System
.Tasking
;
43 package OSI
renames System
.OS_Interface
;
45 procedure Initialize
(Environment_Task
: ST
.Task_Id
);
46 -- Perform initialization and set up of the environment task for proper
47 -- operation of the tasking run-time. This must be called once, before any
48 -- other subprograms of this package are called.
52 Wrapper
: System
.Address
;
53 Stack_Size
: System
.Parameters
.Size_Type
;
54 Priority
: System
.Any_Priority
;
55 Succeeded
: out Boolean);
56 pragma Inline
(Create_Task
);
57 -- Create a new low-level task with ST.Task_Id T and place other needed
58 -- information in the ATCB.
60 -- A new thread of control is created, with a stack of at least Stack_Size
61 -- storage units, and the procedure Wrapper is called by this new thread
62 -- of control. If Stack_Size = Unspecified_Storage_Size, choose a default
63 -- stack size; this may be effectively "unbounded" on some systems.
65 -- The newly created low-level task is associated with the ST.Task_Id T
66 -- such that any subsequent call to Self from within the context of the
67 -- low-level task returns T.
69 -- The caller is responsible for ensuring that the storage of the Ada
70 -- task control block object pointed to by T persists for the lifetime
73 -- Succeeded is set to true unless creation of the task failed,
74 -- as it may if there are insufficient resources to create another task.
76 procedure Enter_Task
(Self_ID
: ST
.Task_Id
);
77 pragma Inline
(Enter_Task
);
78 -- Initialize data structures specific to the calling task. Self must be
79 -- the ID of the calling task. It must be called (once) by the task
80 -- immediately after creation, while abort is still deferred. The effects
81 -- of other operations defined below are not defined unless the caller has
82 -- previously called Initialize_Task.
85 pragma Inline
(Exit_Task
);
86 -- Destroy the thread of control. Self must be the ID of the calling task.
87 -- The effects of further calls to operations defined below on the task
88 -- are undefined thereafter.
90 function New_ATCB
(Entry_Num
: ST
.Task_Entry_Index
) return ST
.Task_Id
;
91 pragma Inline
(New_ATCB
);
92 -- Allocate a new ATCB with the specified number of entries
94 procedure Initialize_TCB
(Self_ID
: ST
.Task_Id
; Succeeded
: out Boolean);
95 pragma Inline
(Initialize_TCB
);
96 -- Initialize all fields of the TCB
98 procedure Finalize_TCB
(T
: ST
.Task_Id
);
99 pragma Inline
(Finalize_TCB
);
100 -- Finalizes Private_Data of ATCB, and then deallocates it. This is also
101 -- responsible for recovering any storage or other resources that were
102 -- allocated by Create_Task (the one in this package). This should only be
103 -- called from Free_Task. After it is called there should be no further
104 -- reference to the ATCB that corresponds to T.
106 procedure Abort_Task
(T
: ST
.Task_Id
);
107 pragma Inline
(Abort_Task
);
108 -- Abort the task specified by T (the target task). This causes the target
109 -- task to asynchronously raise Abort_Signal if abort is not deferred, or
110 -- if it is blocked on an interruptible system call.
113 -- the calling task is holding T's lock and has abort deferred
116 -- the calling task is holding T's lock and has abort deferred.
118 -- ??? modify GNARL to skip wakeup and always call Abort_Task
120 function Self
return ST
.Task_Id
;
121 pragma Inline
(Self
);
122 -- Return a pointer to the Ada Task Control Block of the calling task
129 -- Type used to describe kind of lock for second form of Initialize_Lock
130 -- call specified below. See locking rules in System.Tasking (spec) for
133 procedure Initialize_Lock
134 (Prio
: System
.Any_Priority
;
135 L
: not null access Lock
);
136 procedure Initialize_Lock
137 (L
: not null access RTS_Lock
;
139 pragma Inline
(Initialize_Lock
);
140 -- Initialize a lock object
142 -- For Lock, Prio is the ceiling priority associated with the lock. For
143 -- RTS_Lock, the ceiling is implicitly Priority'Last.
145 -- If the underlying system does not support priority ceiling
146 -- locking, the Prio parameter is ignored.
148 -- The effect of either initialize operation is undefined unless is a lock
149 -- object that has not been initialized, or which has been finalized since
150 -- it was last initialized.
152 -- The effects of the other operations on lock objects are undefined
153 -- unless the lock object has been initialized and has not since been
156 -- Initialization of the per-task lock is implicit in Create_Task
158 -- These operations raise Storage_Error if a lack of storage is detected
160 procedure Finalize_Lock
(L
: not null access Lock
);
161 procedure Finalize_Lock
(L
: not null access RTS_Lock
);
162 pragma Inline
(Finalize_Lock
);
163 -- Finalize a lock object, freeing any resources allocated by the
164 -- corresponding Initialize_Lock operation.
167 (L
: not null access Lock
;
168 Ceiling_Violation
: out Boolean);
170 (L
: not null access RTS_Lock
;
171 Global_Lock
: Boolean := False);
174 pragma Inline
(Write_Lock
);
175 -- Lock a lock object for write access. After this operation returns,
176 -- the calling task holds write permission for the lock object. No other
177 -- Write_Lock or Read_Lock operation on the same lock object will return
178 -- until this task executes an Unlock operation on the same object. The
179 -- effect is undefined if the calling task already holds read or write
180 -- permission for the lock object L.
182 -- For the operation on Lock, Ceiling_Violation is set to true iff the
183 -- operation failed, which will happen if there is a priority ceiling
186 -- For the operation on RTS_Lock, Global_Lock should be set to True
187 -- if L is a global lock (Single_RTS_Lock, Global_Task_Lock).
189 -- For the operation on ST.Task_Id, the lock is the special lock object
190 -- associated with that task's ATCB. This lock has effective ceiling
191 -- priority high enough that it is safe to call by a task with any
192 -- priority in the range System.Priority. It is implicitly initialized
193 -- by task creation. The effect is undefined if the calling task already
194 -- holds T's lock, or has interrupt-level priority. Finalization of the
195 -- per-task lock is implicit in Exit_Task.
198 (L
: not null access Lock
;
199 Ceiling_Violation
: out Boolean);
200 pragma Inline
(Read_Lock
);
201 -- Lock a lock object for read access. After this operation returns,
202 -- the calling task has non-exclusive read permission for the logical
203 -- resources that are protected by the lock. No other Write_Lock operation
204 -- on the same object will return until this task and any other tasks with
205 -- read permission for this lock have executed Unlock operation(s) on the
206 -- lock object. A Read_Lock for a lock object may return immediately while
207 -- there are tasks holding read permission, provided there are no tasks
208 -- holding write permission for the object. The effect is undefined if
209 -- the calling task already holds read or write permission for L.
211 -- Alternatively: An implementation may treat Read_Lock identically to
212 -- Write_Lock. This simplifies the implementation, but reduces the level
213 -- of concurrency that can be achieved.
215 -- Note that Read_Lock is not defined for RT_Lock and ST.Task_Id.
216 -- That is because (1) so far Read_Lock has always been implemented
217 -- the same as Write_Lock, (2) most lock usage inside the RTS involves
218 -- potential write access, and (3) implementations of priority ceiling
219 -- locking that make a reader-writer distinction have higher overhead.
222 (L
: not null access Lock
);
224 (L
: not null access RTS_Lock
;
225 Global_Lock
: Boolean := False);
228 pragma Inline
(Unlock
);
229 -- Unlock a locked lock object
231 -- The effect is undefined unless the calling task holds read or write
232 -- permission for the lock L, and L is the lock object most recently
233 -- locked by the calling task for which the calling task still holds
234 -- read or write permission. (That is, matching pairs of Lock and Unlock
235 -- operations on each lock object must be properly nested.)
237 -- For the operation on RTS_Lock, Global_Lock should be set to True if L
238 -- is a global lock (Single_RTS_Lock, Global_Task_Lock).
240 -- Note that Write_Lock for RTS_Lock does not have an out-parameter.
241 -- RTS_Locks are used in situations where we have not made provision for
242 -- recovery from ceiling violations. We do not expect them to occur inside
243 -- the runtime system, because all RTS locks have ceiling Priority'Last.
245 -- There is one way there can be a ceiling violation. That is if the
246 -- runtime system is called from a task that is executing in the
247 -- Interrupt_Priority range.
249 -- It is not clear what to do about ceiling violations due to RTS calls
250 -- done at interrupt priority. In general, it is not acceptable to give
251 -- all RTS locks interrupt priority, since that would give terrible
252 -- performance on systems where this has the effect of masking hardware
253 -- interrupts, though we could get away allowing Interrupt_Priority'last
254 -- where we are layered on an OS that does not allow us to mask interrupts.
255 -- Ideally, we would like to raise Program_Error back at the original point
256 -- of the RTS call, but this would require a lot of detailed analysis and
257 -- recoding, with almost certain performance penalties.
259 -- For POSIX systems, we considered just skipping setting priority ceiling
260 -- on RTS locks. This would mean there is no ceiling violation, but we
261 -- would end up with priority inversions inside the runtime system,
262 -- resulting in failure to satisfy the Ada priority rules, and possible
263 -- missed validation tests. This could be compensated-for by explicit
264 -- priority-change calls to raise the caller to Priority'Last whenever it
265 -- first enters the runtime system, but the expected overhead seems high,
266 -- though it might be lower than using locks with ceilings if the
267 -- underlying implementation of ceiling locks is an inefficient one.
269 -- This issue should be reconsidered whenever we get around to checking
270 -- for calls to potentially blocking operations from within protected
271 -- operations. If we check for such calls and catch them on entry to the
272 -- OS, it may be that we can eliminate the possibility of ceiling
273 -- violations inside the RTS. For this to work, we would have to forbid
274 -- explicitly setting the priority of a task to anything in the
275 -- Interrupt_Priority range, at least. We would also have to check that
276 -- there are no RTS-lock operations done inside any operations that are
277 -- not treated as potentially blocking.
279 -- The latter approach seems to be the best, i.e. to check on entry to RTS
280 -- calls that may need to use locks that the priority is not in the
281 -- interrupt range. If there are RTS operations that NEED to be called
282 -- from interrupt handlers, those few RTS locks should then be converted
283 -- to PO-type locks, with ceiling Interrupt_Priority'Last.
285 -- For now, we will just shut down the system if there is ceiling violation
287 procedure Set_Ceiling
288 (L
: not null access Lock
;
289 Prio
: System
.Any_Priority
);
290 pragma Inline
(Set_Ceiling
);
291 -- Change the ceiling priority associated to the lock
293 -- The effect is undefined unless the calling task holds read or write
294 -- permission for the lock L, and L is the lock object most recently
295 -- locked by the calling task for which the calling task still holds
296 -- read or write permission. (That is, matching pairs of Lock and Unlock
297 -- operations on each lock object must be properly nested.)
299 procedure Yield
(Do_Yield
: Boolean := True);
300 pragma Inline
(Yield
);
301 -- Yield the processor. Add the calling task to the tail of the ready
302 -- queue for its active_priority. The Do_Yield argument is only used in
303 -- some very rare cases very a yield should have an effect on a specific
304 -- target and not on regular ones.
306 procedure Set_Priority
308 Prio
: System
.Any_Priority
;
309 Loss_Of_Inheritance
: Boolean := False);
310 pragma Inline
(Set_Priority
);
311 -- Set the priority of the task specified by T to T.Current_Priority. The
312 -- priority set is what would correspond to the Ada concept of "base
313 -- priority" in the terms of the lower layer system, but the operation may
314 -- be used by the upper layer to implement changes in "active priority"
315 -- that are not due to lock effects. The effect should be consistent with
316 -- the Ada Reference Manual. In particular, when a task lowers its
317 -- priority due to the loss of inherited priority, it goes at the head of
318 -- the queue for its new priority (RM D.2.2 par 9). Loss_Of_Inheritance
319 -- helps the underlying implementation to do it right when the OS doesn't.
321 function Get_Priority
(T
: ST
.Task_Id
) return System
.Any_Priority
;
322 pragma Inline
(Get_Priority
);
323 -- Returns the priority last set by Set_Priority for this task
325 function Monotonic_Clock
return Duration;
326 pragma Inline
(Monotonic_Clock
);
327 -- Returns "absolute" time, represented as an offset relative to "the
328 -- Epoch", which is Jan 1, 1970. This clock implementation is immune to
329 -- the system's clock changes.
331 function RT_Resolution
return Duration;
332 pragma Inline
(RT_Resolution
);
333 -- Returns resolution of the underlying clock used to implement RT_Clock
339 -- Whoever calls either of the Sleep routines is responsible for checking
340 -- for pending aborts before the call. Pending priority changes are handled
344 (Self_ID
: ST
.Task_Id
;
345 Reason
: System
.Tasking
.Task_States
);
346 pragma Inline
(Sleep
);
347 -- Wait until the current task, T, is signaled to wake up
350 -- The calling task is holding its own ATCB lock
351 -- and has abort deferred
354 -- The calling task is holding its own ATCB lock and has abort deferred.
356 -- The effect is to atomically unlock T's lock and wait, so that another
357 -- task that is able to lock T's lock can be assured that the wait has
358 -- actually commenced, and that a Wakeup operation will cause the waiting
359 -- task to become ready for execution once again. When Sleep returns, the
360 -- waiting task will again hold its own ATCB lock. The waiting task may
361 -- become ready for execution at any time (that is, spurious wakeups are
362 -- permitted), but it will definitely become ready for execution when a
363 -- Wakeup operation is performed for the same task.
365 procedure Timed_Sleep
366 (Self_ID
: ST
.Task_Id
;
368 Mode
: ST
.Delay_Modes
;
369 Reason
: System
.Tasking
.Task_States
;
370 Timedout
: out Boolean;
371 Yielded
: out Boolean);
372 -- Combination of Sleep (above) and Timed_Delay
374 procedure Timed_Delay
375 (Self_ID
: ST
.Task_Id
;
377 Mode
: ST
.Delay_Modes
);
378 -- Implement the semantics of the delay statement.
379 -- The caller should be abort-deferred and should not hold any locks.
383 Reason
: System
.Tasking
.Task_States
);
384 pragma Inline
(Wakeup
);
385 -- Wake up task T if it is waiting on a Sleep call (of ordinary
386 -- or timed variety), making it ready for execution once again.
387 -- If the task T is not waiting on a Sleep, the operation has no effect.
389 function Environment_Task
return ST
.Task_Id
;
390 pragma Inline
(Environment_Task
);
391 -- Return the task ID of the environment task
392 -- Consider putting this into a variable visible directly
393 -- by the rest of the runtime system. ???
395 function Get_Thread_Id
(T
: ST
.Task_Id
) return OSI
.Thread_Id
;
396 -- Return the thread id of the specified task
398 function Is_Valid_Task
return Boolean;
399 pragma Inline
(Is_Valid_Task
);
400 -- Does the calling thread have an ATCB?
402 function Register_Foreign_Thread
return ST
.Task_Id
;
403 -- Allocate and initialize a new ATCB for the current thread
405 -----------------------
406 -- RTS Entrance/Exit --
407 -----------------------
409 -- Following two routines are used for possible operations needed to be
410 -- setup/cleared upon entrance/exit of RTS while maintaining a single
411 -- thread of control in the RTS. Since we intend these routines to be used
412 -- for implementing the Single_Lock RTS, Lock_RTS should follow the first
413 -- Defer_Abort operation entering RTS. In the same fashion Unlock_RTS
414 -- should precede the last Undefer_Abort exiting RTS.
416 -- These routines also replace the functions Lock/Unlock_All_Tasks_List
419 -- Take the global RTS lock
421 procedure Unlock_RTS
;
422 -- Release the global RTS lock
428 -- Stack checking in GNAT is done using the concept of stack probes. A
429 -- stack probe is an operation that will generate a storage error if
430 -- an insufficient amount of stack space remains in the current task.
432 -- The exact mechanism for a stack probe is target dependent. Typical
433 -- possibilities are to use a load from a non-existent page, a store to a
434 -- read-only page, or a comparison with some stack limit constant. Where
435 -- possible we prefer to use a trap on a bad page access, since this has
436 -- less overhead. The generation of stack probes is either automatic if
437 -- the ABI requires it (as on for example DEC Unix), or is controlled by
438 -- the gcc parameter -fstack-check.
440 -- When we are using bad-page accesses, we need a bad page, called guard
441 -- page, at the end of each task stack. On some systems, this is provided
442 -- automatically, but on other systems, we need to create the guard page
443 -- ourselves, and the procedure Stack_Guard is provided for this purpose.
445 procedure Stack_Guard
(T
: ST
.Task_Id
; On
: Boolean);
446 -- Ensure guard page is set if one is needed and the underlying thread
447 -- system does not provide it. The procedure is as follows:
449 -- 1. When we create a task adjust its size so a guard page can
450 -- safely be set at the bottom of the stack.
452 -- 2. When the thread is created (and its stack allocated by the
453 -- underlying thread system), get the stack base (and size, depending
454 -- how the stack is growing), and create the guard page taking care
455 -- of page boundaries issues.
457 -- 3. When the task is destroyed, remove the guard page.
459 -- If On is true then protect the stack bottom (i.e make it read only)
460 -- else unprotect it (i.e. On is True for the call when creating a task,
461 -- and False when a task is destroyed).
463 -- The call to Stack_Guard has no effect if guard pages are not used on
464 -- the target, or if guard pages are automatically provided by the system.
466 ------------------------
467 -- Suspension objects --
468 ------------------------
470 -- These subprograms provide the functionality required for synchronizing
471 -- on a suspension object. Tasks can suspend execution and relinquish the
472 -- processors until the condition is signaled.
474 function Current_State
(S
: Suspension_Object
) return Boolean;
475 -- Return the state of the suspension object
477 procedure Set_False
(S
: in out Suspension_Object
);
478 -- Set the state of the suspension object to False
480 procedure Set_True
(S
: in out Suspension_Object
);
481 -- Set the state of the suspension object to True. If a task were
482 -- suspended on the protected object then this task is released (and
483 -- the state of the suspension object remains set to False).
485 procedure Suspend_Until_True
(S
: in out Suspension_Object
);
486 -- If the state of the suspension object is True then the calling task
487 -- continues its execution, and the state is set to False. If the state
488 -- of the object is False then the task is suspended on the suspension
489 -- object until a Set_True operation is executed. Program_Error is raised
490 -- if another task is already waiting on that suspension object.
492 procedure Initialize
(S
: in out Suspension_Object
);
493 -- Initialize the suspension object
495 procedure Finalize
(S
: in out Suspension_Object
);
496 -- Finalize the suspension object
498 -----------------------------------------
499 -- Runtime System Debugging Interfaces --
500 -----------------------------------------
502 -- These interfaces have been added to assist in debugging the
503 -- tasking runtime system.
505 function Check_Exit
(Self_ID
: ST
.Task_Id
) return Boolean;
506 pragma Inline
(Check_Exit
);
507 -- Check that the current task is holding only Global_Task_Lock
509 function Check_No_Locks
(Self_ID
: ST
.Task_Id
) return Boolean;
510 pragma Inline
(Check_No_Locks
);
511 -- Check that current task is holding no locks
513 function Suspend_Task
515 Thread_Self
: OSI
.Thread_Id
) return Boolean;
516 -- Suspend a specific task when the underlying thread library provides this
517 -- functionality, unless the thread associated with T is Thread_Self. Such
518 -- functionality is needed by gdb on some targets (e.g VxWorks) Return True
519 -- is the operation is successful. On targets where this operation is not
520 -- available, a dummy body is present which always returns False.
524 Thread_Self
: OSI
.Thread_Id
) return Boolean;
525 -- Resume a specific task when the underlying thread library provides
526 -- such functionality, unless the thread associated with T is Thread_Self.
527 -- Such functionality is needed by gdb on some targets (e.g VxWorks)
528 -- Return True is the operation is successful
530 procedure Stop_All_Tasks
;
531 -- Stop all tasks when the underlying thread library provides such
532 -- functionality. Such functionality is needed by gdb on some targets (e.g
533 -- VxWorks) This function can be run from an interrupt handler. Return True
534 -- is the operation is successful
536 function Stop_Task
(T
: ST
.Task_Id
) return Boolean;
537 -- Stop a specific task when the underlying thread library provides
538 -- such functionality. Such functionality is needed by gdb on some targets
539 -- (e.g VxWorks). Return True is the operation is successful.
541 function Continue_Task
(T
: ST
.Task_Id
) return Boolean;
542 -- Continue a specific task when the underlying thread library provides
543 -- such functionality. Such functionality is needed by gdb on some targets
544 -- (e.g VxWorks) Return True is the operation is successful
546 end System
.Task_Primitives
.Operations
;