1------------------------------------------------------------------------------
2--                                                                          --
3--                GNU ADA RUN-TIME LIBRARY (GNARL) COMPONENTS               --
4--                                                                          --
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     --
6--                                                                          --
7--                                  S p e c                                 --
8--                                                                          --
9--          Copyright (C) 1992-2020, 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------------------------------------------------------------------------------
31
32--  This package contains all the GNULL primitives that interface directly with
33--  the underlying OS.
34
35with System.Parameters;
36with System.Tasking;
37with System.OS_Interface;
38
39package System.Task_Primitives.Operations is
40   pragma Preelaborate;
41
42   package ST renames System.Tasking;
43   package OSI renames System.OS_Interface;
44
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.
49
50   procedure Create_Task
51     (T          : ST.Task_Id;
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.
59   --
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.
64   --
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.
68   --
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
71   --  of the new task.
72   --
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.
75
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.
83
84   procedure Exit_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.
89
90   ----------------------------------
91   -- ATCB allocation/deallocation --
92   ----------------------------------
93
94   package ATCB_Allocation is
95
96      function New_ATCB (Entry_Num : ST.Task_Entry_Index) return ST.Task_Id;
97      pragma Inline (New_ATCB);
98      --  Allocate a new ATCB with the specified number of entries
99
100      procedure Free_ATCB (T : ST.Task_Id);
101      pragma Inline (Free_ATCB);
102      --  Deallocate an ATCB previously allocated by New_ATCB
103
104   end ATCB_Allocation;
105
106   function New_ATCB (Entry_Num : ST.Task_Entry_Index) return ST.Task_Id
107     renames ATCB_Allocation.New_ATCB;
108
109   procedure Initialize_TCB (Self_ID : ST.Task_Id; Succeeded : out Boolean);
110   pragma Inline (Initialize_TCB);
111   --  Initialize all fields of the TCB
112
113   procedure Finalize_TCB (T : ST.Task_Id);
114   pragma Inline (Finalize_TCB);
115   --  Finalizes Private_Data of ATCB, and then deallocates it. This is also
116   --  responsible for recovering any storage or other resources that were
117   --  allocated by Create_Task (the one in this package). This should only be
118   --  called from Free_Task. After it is called there should be no further
119   --  reference to the ATCB that corresponds to T.
120
121   procedure Abort_Task (T : ST.Task_Id);
122   pragma Inline (Abort_Task);
123   --  Abort the task specified by T (the target task). This causes the target
124   --  task to asynchronously raise Abort_Signal if abort is not deferred, or
125   --  if it is blocked on an interruptible system call.
126   --
127   --  precondition:
128   --    the calling task is holding T's lock and has abort deferred
129   --
130   --  postcondition:
131   --    the calling task is holding T's lock and has abort deferred.
132
133   --  ??? modify GNARL to skip wakeup and always call Abort_Task
134
135   function Self return ST.Task_Id;
136   pragma Inline (Self);
137   --  Return a pointer to the Ada Task Control Block of the calling task
138
139   type Lock_Level is
140     (PO_Level,
141      Global_Task_Level,
142      RTS_Lock_Level,
143      ATCB_Level);
144   --  Type used to describe kind of lock for second form of Initialize_Lock
145   --  call specified below. See locking rules in System.Tasking (spec) for
146   --  more details.
147
148   procedure Initialize_Lock
149     (Prio : System.Any_Priority;
150      L    : not null access Lock);
151   procedure Initialize_Lock
152     (L     : not null access RTS_Lock;
153      Level : Lock_Level);
154   pragma Inline (Initialize_Lock);
155   --  Initialize a lock object
156   --
157   --  For Lock, Prio is the ceiling priority associated with the lock. For
158   --  RTS_Lock, the ceiling is implicitly Priority'Last.
159   --
160   --  If the underlying system does not support priority ceiling
161   --  locking, the Prio parameter is ignored.
162   --
163   --  The effect of either initialize operation is undefined unless is a lock
164   --  object that has not been initialized, or which has been finalized since
165   --  it was last initialized.
166   --
167   --  The effects of the other operations on lock objects are undefined
168   --  unless the lock object has been initialized and has not since been
169   --  finalized.
170   --
171   --  Initialization of the per-task lock is implicit in Create_Task
172   --
173   --  These operations raise Storage_Error if a lack of storage is detected
174
175   procedure Finalize_Lock (L : not null access Lock);
176   procedure Finalize_Lock (L : not null access RTS_Lock);
177   pragma Inline (Finalize_Lock);
178   --  Finalize a lock object, freeing any resources allocated by the
179   --  corresponding Initialize_Lock operation.
180
181   procedure Write_Lock
182     (L                 : not null access Lock;
183      Ceiling_Violation : out Boolean);
184   procedure Write_Lock (L : not null access RTS_Lock);
185   procedure Write_Lock (T : ST.Task_Id);
186   pragma Inline (Write_Lock);
187   --  Lock a lock object for write access. After this operation returns,
188   --  the calling task holds write permission for the lock object. No other
189   --  Write_Lock or Read_Lock operation on the same lock object will return
190   --  until this task executes an Unlock operation on the same object. The
191   --  effect is undefined if the calling task already holds read or write
192   --  permission for the lock object L.
193   --
194   --  For the operation on Lock, Ceiling_Violation is set to true iff the
195   --  operation failed, which will happen if there is a priority ceiling
196   --  violation.
197   --
198   --  For the operation on ST.Task_Id, the lock is the special lock object
199   --  associated with that task's ATCB. This lock has effective ceiling
200   --  priority high enough that it is safe to call by a task with any
201   --  priority in the range System.Priority. It is implicitly initialized
202   --  by task creation. The effect is undefined if the calling task already
203   --  holds T's lock, or has interrupt-level priority. Finalization of the
204   --  per-task lock is implicit in Exit_Task.
205
206   procedure Read_Lock
207     (L                 : not null access Lock;
208      Ceiling_Violation : out Boolean);
209   pragma Inline (Read_Lock);
210   --  Lock a lock object for read access. After this operation returns,
211   --  the calling task has non-exclusive read permission for the logical
212   --  resources that are protected by the lock. No other Write_Lock operation
213   --  on the same object will return until this task and any other tasks with
214   --  read permission for this lock have executed Unlock operation(s) on the
215   --  lock object. A Read_Lock for a lock object may return immediately while
216   --  there are tasks holding read permission, provided there are no tasks
217   --  holding write permission for the object. The effect is undefined if
218   --  the calling task already holds read or write permission for L.
219   --
220   --  Alternatively: An implementation may treat Read_Lock identically to
221   --  Write_Lock. This simplifies the implementation, but reduces the level
222   --  of concurrency that can be achieved.
223   --
224   --  Note that Read_Lock is not defined for RT_Lock and ST.Task_Id.
225   --  That is because (1) so far Read_Lock has always been implemented
226   --  the same as Write_Lock, (2) most lock usage inside the RTS involves
227   --  potential write access, and (3) implementations of priority ceiling
228   --  locking that make a reader-writer distinction have higher overhead.
229
230   procedure Unlock
231     (L : not null access Lock);
232   procedure Unlock (L : not null access RTS_Lock);
233   procedure Unlock (T : ST.Task_Id);
234   pragma Inline (Unlock);
235   --  Unlock a locked lock object
236   --
237   --  The effect is undefined unless the calling task holds read or write
238   --  permission for the lock L, and L is the lock object most recently
239   --  locked by the calling task for which the calling task still holds
240   --  read or write permission. (That is, matching pairs of Lock and Unlock
241   --  operations on each lock object must be properly nested.)
242
243   --  Note that Write_Lock for RTS_Lock does not have an out-parameter.
244   --  RTS_Locks are used in situations where we have not made provision for
245   --  recovery from ceiling violations. We do not expect them to occur inside
246   --  the runtime system, because all RTS locks have ceiling Priority'Last.
247
248   --  There is one way there can be a ceiling violation. That is if the
249   --  runtime system is called from a task that is executing in the
250   --  Interrupt_Priority range.
251
252   --  It is not clear what to do about ceiling violations due to RTS calls
253   --  done at interrupt priority. In general, it is not acceptable to give
254   --  all RTS locks interrupt priority, since that would give terrible
255   --  performance on systems where this has the effect of masking hardware
256   --  interrupts, though we could get away allowing Interrupt_Priority'last
257   --  where we are layered on an OS that does not allow us to mask interrupts.
258   --  Ideally, we would like to raise Program_Error back at the original point
259   --  of the RTS call, but this would require a lot of detailed analysis and
260   --  recoding, with almost certain performance penalties.
261
262   --  For POSIX systems, we considered just skipping setting priority ceiling
263   --  on RTS locks. This would mean there is no ceiling violation, but we
264   --  would end up with priority inversions inside the runtime system,
265   --  resulting in failure to satisfy the Ada priority rules, and possible
266   --  missed validation tests. This could be compensated-for by explicit
267   --  priority-change calls to raise the caller to Priority'Last whenever it
268   --  first enters the runtime system, but the expected overhead seems high,
269   --  though it might be lower than using locks with ceilings if the
270   --  underlying implementation of ceiling locks is an inefficient one.
271
272   --  This issue should be reconsidered whenever we get around to checking
273   --  for calls to potentially blocking operations from within protected
274   --  operations. If we check for such calls and catch them on entry to the
275   --  OS, it may be that we can eliminate the possibility of ceiling
276   --  violations inside the RTS. For this to work, we would have to forbid
277   --  explicitly setting the priority of a task to anything in the
278   --  Interrupt_Priority range, at least. We would also have to check that
279   --  there are no RTS-lock operations done inside any operations that are
280   --  not treated as potentially blocking.
281
282   --  The latter approach seems to be the best, i.e. to check on entry to RTS
283   --  calls that may need to use locks that the priority is not in the
284   --  interrupt range. If there are RTS operations that NEED to be called
285   --  from interrupt handlers, those few RTS locks should then be converted
286   --  to PO-type locks, with ceiling Interrupt_Priority'Last.
287
288   --  For now, we will just shut down the system if there is ceiling violation
289
290   procedure Set_Ceiling
291     (L    : not null access Lock;
292      Prio : System.Any_Priority);
293   pragma Inline (Set_Ceiling);
294   --  Change the ceiling priority associated to the lock
295   --
296   --  The effect is undefined unless the calling task holds read or write
297   --  permission for the lock L, and L is the lock object most recently
298   --  locked by the calling task for which the calling task still holds
299   --  read or write permission. (That is, matching pairs of Lock and Unlock
300   --  operations on each lock object must be properly nested.)
301
302   procedure Yield (Do_Yield : Boolean := True);
303   pragma Inline (Yield);
304   --  Yield the processor. Add the calling task to the tail of the ready queue
305   --  for its active_priority. On most platforms, Yield is a no-op if Do_Yield
306   --  is False. But on some platforms (notably VxWorks), Do_Yield is ignored.
307   --  This is only used in some very rare cases where a Yield should have an
308   --  effect on a specific target and not on regular ones.
309
310   procedure Set_Priority
311     (T : ST.Task_Id;
312      Prio : System.Any_Priority;
313      Loss_Of_Inheritance : Boolean := False);
314   pragma Inline (Set_Priority);
315   --  Set the priority of the task specified by T to Prio. The priority set
316   --  is what would correspond to the Ada concept of "base priority" in the
317   --  terms of the lower layer system, but the operation may be used by the
318   --  upper layer to implement changes in "active priority" that are not due
319   --  to lock effects. The effect should be consistent with the Ada Reference
320   --  Manual. In particular, when a task lowers its priority due to the loss
321   --  of inherited priority, it goes at the head of the queue for its new
322   --  priority (RM D.2.2 par 9). Loss_Of_Inheritance helps the underlying
323   --  implementation to do it right when the OS doesn't.
324
325   function Get_Priority (T : ST.Task_Id) return System.Any_Priority;
326   pragma Inline (Get_Priority);
327   --  Returns the priority last set by Set_Priority for this task
328
329   function Monotonic_Clock return Duration;
330   pragma Inline (Monotonic_Clock);
331   --  Returns "absolute" time, represented as an offset relative to an
332   --  unspecified Epoch. This clock implementation is immune to the
333   --  system's clock changes.
334
335   function RT_Resolution return Duration;
336   pragma Inline (RT_Resolution);
337   --  Returns resolution of the underlying clock used to implement RT_Clock
338
339   ----------------
340   -- Extensions --
341   ----------------
342
343   --  Whoever calls either of the Sleep routines is responsible for checking
344   --  for pending aborts before the call. Pending priority changes are handled
345   --  internally.
346
347   procedure Sleep
348     (Self_ID : ST.Task_Id;
349      Reason  : System.Tasking.Task_States);
350   pragma Inline (Sleep);
351   --  Wait until the current task, T,  is signaled to wake up
352   --
353   --  precondition:
354   --    The calling task is holding its own ATCB lock
355   --    and has abort deferred
356   --
357   --  postcondition:
358   --    The calling task is holding its own ATCB lock and has abort deferred.
359
360   --  The effect is to atomically unlock T's lock and wait, so that another
361   --  task that is able to lock T's lock can be assured that the wait has
362   --  actually commenced, and that a Wakeup operation will cause the waiting
363   --  task to become ready for execution once again. When Sleep returns, the
364   --  waiting task will again hold its own ATCB lock. The waiting task may
365   --  become ready for execution at any time (that is, spurious wakeups are
366   --  permitted), but it will definitely become ready for execution when a
367   --  Wakeup operation is performed for the same task.
368
369   procedure Timed_Sleep
370     (Self_ID  : ST.Task_Id;
371      Time     : Duration;
372      Mode     : ST.Delay_Modes;
373      Reason   : System.Tasking.Task_States;
374      Timedout : out Boolean;
375      Yielded  : out Boolean);
376   --  Combination of Sleep (above) and Timed_Delay
377
378   procedure Timed_Delay
379     (Self_ID : ST.Task_Id;
380      Time    : Duration;
381      Mode    : ST.Delay_Modes);
382   --  Implement the semantics of the delay statement.
383   --  The caller should be abort-deferred and should not hold any locks.
384
385   procedure Wakeup
386     (T      : ST.Task_Id;
387      Reason : System.Tasking.Task_States);
388   pragma Inline (Wakeup);
389   --  Wake up task T if it is waiting on a Sleep call (of ordinary
390   --  or timed variety), making it ready for execution once again.
391   --  If the task T is not waiting on a Sleep, the operation has no effect.
392
393   function Environment_Task return ST.Task_Id;
394   pragma Inline (Environment_Task);
395   --  Return the task ID of the environment task
396   --  Consider putting this into a variable visible directly
397   --  by the rest of the runtime system. ???
398
399   function Get_Thread_Id (T : ST.Task_Id) return OSI.Thread_Id;
400   --  Return the thread id of the specified task
401
402   function Is_Valid_Task return Boolean;
403   pragma Inline (Is_Valid_Task);
404   --  Does the calling thread have an ATCB?
405
406   function Register_Foreign_Thread return ST.Task_Id;
407   --  Allocate and initialize a new ATCB for the current thread
408
409   -----------------------
410   -- RTS Entrance/Exit --
411   -----------------------
412
413   --  Following two routines are used for possible operations needed to be
414   --  setup/cleared upon entrance/exit of RTS while maintaining a single
415   --  thread of control in the RTS.
416   --
417   --  These routines also replace the functions Lock/Unlock_All_Tasks_List
418
419   procedure Lock_RTS;
420   --  Take the global RTS lock
421
422   procedure Unlock_RTS;
423   --  Release the global RTS lock
424
425   --------------------
426   -- Stack Checking --
427   --------------------
428
429   --  Stack checking in GNAT is done using the concept of stack probes. A
430   --  stack probe is an operation that will generate a storage error if
431   --  an insufficient amount of stack space remains in the current task.
432
433   --  The exact mechanism for a stack probe is target dependent. Typical
434   --  possibilities are to use a load from a non-existent page, a store to a
435   --  read-only page, or a comparison with some stack limit constant. Where
436   --  possible we prefer to use a trap on a bad page access, since this has
437   --  less overhead. The generation of stack probes is either automatic if
438   --  the ABI requires it (as on for example DEC Unix), or is controlled by
439   --  the gcc parameter -fstack-check.
440
441   --  When we are using bad-page accesses, we need a bad page, called guard
442   --  page, at the end of each task stack. On some systems, this is provided
443   --  automatically, but on other systems, we need to create the guard page
444   --  ourselves, and the procedure Stack_Guard is provided for this purpose.
445
446   procedure Stack_Guard (T : ST.Task_Id; On : Boolean);
447   --  Ensure guard page is set if one is needed and the underlying thread
448   --  system does not provide it. The procedure is as follows:
449   --
450   --    1. When we create a task adjust its size so a guard page can
451   --       safely be set at the bottom of the stack.
452   --
453   --    2. When the thread is created (and its stack allocated by the
454   --       underlying thread system), get the stack base (and size, depending
455   --       how the stack is growing), and create the guard page taking care
456   --       of page boundaries issues.
457   --
458   --    3. When the task is destroyed, remove the guard page.
459   --
460   --  If On is true then protect the stack bottom (i.e make it read only)
461   --  else unprotect it (i.e. On is True for the call when creating a task,
462   --  and False when a task is destroyed).
463   --
464   --  The call to Stack_Guard has no effect if guard pages are not used on
465   --  the target, or if guard pages are automatically provided by the system.
466
467   ------------------------
468   -- Suspension objects --
469   ------------------------
470
471   --  These subprograms provide the functionality required for synchronizing
472   --  on a suspension object. Tasks can suspend execution and relinquish the
473   --  processors until the condition is signaled.
474
475   function Current_State (S : Suspension_Object) return Boolean;
476   --  Return the state of the suspension object
477
478   procedure Set_False (S : in out Suspension_Object);
479   --  Set the state of the suspension object to False
480
481   procedure Set_True (S : in out Suspension_Object);
482   --  Set the state of the suspension object to True. If a task were
483   --  suspended on the protected object then this task is released (and
484   --  the state of the suspension object remains set to False).
485
486   procedure Suspend_Until_True (S : in out Suspension_Object);
487   --  If the state of the suspension object is True then the calling task
488   --  continues its execution, and the state is set to False. If the state
489   --  of the object is False then the task is suspended on the suspension
490   --  object until a Set_True operation is executed. Program_Error is raised
491   --  if another task is already waiting on that suspension object.
492
493   procedure Initialize (S : in out Suspension_Object);
494   --  Initialize the suspension object
495
496   procedure Finalize (S : in out Suspension_Object);
497   --  Finalize the suspension object
498
499   -----------------------------------------
500   -- Runtime System Debugging Interfaces --
501   -----------------------------------------
502
503   --  These interfaces have been added to assist in debugging the
504   --  tasking runtime system.
505
506   function Check_Exit (Self_ID : ST.Task_Id) return Boolean;
507   pragma Inline (Check_Exit);
508   --  Check that the current task is holding only Global_Task_Lock
509
510   function Check_No_Locks (Self_ID : ST.Task_Id) return Boolean;
511   pragma Inline (Check_No_Locks);
512   --  Check that current task is holding no locks
513
514   function Suspend_Task
515     (T           : ST.Task_Id;
516      Thread_Self : OSI.Thread_Id) return Boolean;
517   --  Suspend a specific task when the underlying thread library provides this
518   --  functionality, unless the thread associated with T is Thread_Self. Such
519   --  functionality is needed by gdb on some targets (e.g VxWorks) Return True
520   --  is the operation is successful. On targets where this operation is not
521   --  available, a dummy body is present which always returns False.
522
523   function Resume_Task
524     (T           : ST.Task_Id;
525      Thread_Self : OSI.Thread_Id) return Boolean;
526   --  Resume a specific task when the underlying thread library provides
527   --  such functionality, unless the thread associated with T is Thread_Self.
528   --  Such functionality is needed by gdb on some targets (e.g VxWorks)
529   --  Return True is the operation is successful
530
531   procedure Stop_All_Tasks;
532   --  Stop all tasks when the underlying thread library provides such
533   --  functionality. Such functionality is needed by gdb on some targets (e.g
534   --  VxWorks) This function can be run from an interrupt handler. Return True
535   --  is the operation is successful
536
537   function Stop_Task (T : ST.Task_Id) return Boolean;
538   --  Stop a specific task when the underlying thread library provides
539   --  such functionality. Such functionality is needed by gdb on some targets
540   --  (e.g VxWorks). Return True is the operation is successful.
541
542   function Continue_Task (T : ST.Task_Id) return Boolean;
543   --  Continue a specific task when the underlying thread library provides
544   --  such functionality. Such functionality is needed by gdb on some targets
545   --  (e.g VxWorks) Return True is the operation is successful
546
547   -------------------
548   -- Task affinity --
549   -------------------
550
551   procedure Set_Task_Affinity (T : ST.Task_Id);
552   --  Enforce at the operating system level the task affinity defined in the
553   --  Ada Task Control Block. Has no effect if the underlying operating system
554   --  does not support this capability.
555
556end System.Task_Primitives.Operations;
557