Tasking and Blocking Calls and Clean Termination

Hi,

I’m used to C/C++, learning Ada, I’m trying to implement a tetris clone.

I didn’t want to bother with a GUI framework initially, so I started with basic CLI primitives:

  • Each “frame” I just Ada.Text_IO.Put_Line to blast out the “playing field”
  • Using Ada.Text_IO.Get_Immediate to get input from the user. (Later using ada-evdev Read to get keypress events)

In order to receive the inputs from the user asynchronously, I created a separate task, which worked ok but I ran into the interesting
difference between C++ and ada: An unhandled exception doesn’t automatically terminate the program. Ok, I think its good to clean everything up anyways.

So now I end up with the following statements:

  1. I would prefer to use a blocking function for getting inputs, rather than one that does a nonblocking operation in a loop with a very short delay.
    (That would probably lead to many unnecessary context switches/syscalls? Lot of unnecessary CPU time spent spinning waiting for input?)
  2. I would like to be able to signal my thread to do any cleanup and then exit
    (maybe read any pending stdin characters and termios re-enable echo so the terminal isn’t weird when the program exits)

What is a reasonable way of doing this?

This issue probably also applies to things like network IO from sockets, but I haven’t done any socket programming in Ada yet… but I guess the story would be:

  1. I have a dedicated task for handling incoming connections and traffic.
  2. It’s blocked waiting for some client input (or some timeout?).
  3. I get an exception in some other thread and want to exit immediately.

Is throwing an abort at the blocked task the best option?
e.g.

  1. Add a handler for task termination
  2. make the non-blocking part of the task subprogram some abort-deferred block? (protected something?)

so I know that if I throw an abort at it, if it was already doing something, it will finish that thing before being kicked to the termination handler?

The reasonable way is not to use terminal I/O for the purpose. The terminal I/O is heavily dependent on the OS and terminal emulation (e.g. VT100) inside the OS. Aborting a task blocked by the OS is a bad idea too.

Regarding the sockets, to end the blocking I/O from outside the socket is closed. This cancels waiting.

I suppose the same technique can be used for a serial port I/O. Close the serial port file. Also see the package GNAT.Serial_Communications.

P.S. Any time invested into terminal I/O is 100% wasted. Start with any Ada GUI there are lots of them. E.g. native graphics GtkAda + Cairo (here). Or if you choose web-based gnoga you will find a tetris game implementation there.

It’s a bit dismissive to say that time invested into terminal I/O is 100% wasted. Computer programs (games especially) are whatever you want them to be.

I am also now using ada-evdev (arrow keys from keyboard, or potentially gamepad).

Closing the evdev input file does seem like a reasonable option, but is somewhat indirect, so it didn’t immediately occur to me.

Thanks!

1 Like

Don’t be offended, it is a well-trodden path. You are not the first one going down this dead end road… :slightly_smiling_face:

For the termination question: One thing you can kind of do is make a “reverse” watch dog timer like object. Basically a Boolean that is initialized one way and as long as it stays that way, all tasks run. If a task has an exception, in the handler have it flip the boolean to the non initialized value and all the tasks can manually terminate if they see it change.

You can either use a protected type for this:

protected Watchdog is
   function Status_OK return Boolean;
   procedure Set_Not_OK;
private
   OK : Boolean := True;
end Watchdog;

protected body Watchdog is
   function Status_OK return Boolean is
   begin
      return OK;
   end Status_OK;

   procedure Set_Not_OK is
   begin
      OK := False;
   end Set_Not_OK;
end Watchdog;

or since a Boolean is atomic on probably any platform and you only change it once per platform (to signal global termination) you can just declare an atomic boolean variable:

Status_OK : Boolean := True with Atomic;

There’s probably a creative way to do it with Rendezvous too, but that was just the first thing that came to mind.

After doing some testing and poking around online, I think the behaviour of closing a FD that is being waited on isn’t reliable. In the case of monitoring evdev/stdin, the call doesn’t actually return until another character is typed.
I think this might be because the read syscall also keeps a refcount on the open file descriptor object.

You may also run into the classic race condition where the underlying file descriptors are reused. (If you just want to end some subsystem as opposed to taking down your entire program).

Any other potential solutions?

EDIT: One thing you can do with linux syscalls is any time you want your blocking state to be interruptible is to create a pipe and add it to an epoll instance (or select I guess). That way, another thread can write to the pipe to wake up your thread.

The Ada standard libraries don’t implement anything like this though.

Cancellable Read POC

The FDs have to all be made O_NONBLOCK.

    ssize_t Read(void *buf, ssize_t buflen) {
        
        ssize_t total_read = 0;
        unsigned char *ptr = (unsigned char *)buf;
        struct epoll_event events[max_events];
        while (buflen > 0) {
            int nfds = epoll_wait(mEpollFd, events, max_events, -1);
            assert(nfds != -1);
            for (int i = 0; i < nfds; ++i) {
                int const efd = events[i].data.fd;
                if (efd == mMainFd) {
                    ssize_t rd = read(mMainFd, ptr, buflen);
                    if ((rd == -1) && ((errno == EAGAIN) || (errno == EWOULDBLOCK))) {
                        continue;
                    }
                    total_read += rd;
                    buflen -= rd;
                    ptr += rd;
                } else if (efd == mWakeRead) {
                    unsigned char dat[256];
                    while (read(mWakeRead, dat, sizeof(dat)) > 0) {}
                    if (total_read == 0) {
                        errno = EINTR;
                        return -1;
                    }   
                    return total_read;
                }
            }
        }
        return total_read;
    }

What you’re looking for is handled by Ada.Task_Termination. See this.

Yes, you can register a specific handler for your task that runs on termination, but the task won’t terminate if its blocked.

One idea I theorized was to use abort-deferred regions to protect some operations, and then abort to kick the task out of the blocking state into the termination handler. This seems a bit kludgy though

Hm, I would suggest doing a keyboard/input protocol task.

-- Assuming:
Type Direction is (None, Up, Down, Left, Right);

Task Interface Get_Input;
Procedure Done          ( Object : in Get_Input );
Procedure Read_Signal   ( Object : in Get_Input );
Procedure Read_Direction( Object : in Get_Input; Value : out Direction );
Function  Get_Direction ( Object : in Get_Input'Class ) return Direction;
---------
-- USE THIS FUNCTION FOR YOUR PUBLIC INTERFACING.
Function  Get_Direction ( Object : in Get_Input'Class ) return Direction is
Begin
  Return Result : Direction := None do
     Object.Read_Signal;
     Object.Read_Direction( Result );
  End return;
End Get_Direction;
---------
Task Type Keyboard_Input is new Get_Input with
   Entry Read_Signal;
   Entry Read_Direction( X : out Direction);
End Get_Input;

Task Body Get_Input is
  Finished : Boolean := False;
  Signal    : Keyboard_code; -- Whatever type.
Begin
  Loop
    Exit when Finished;
    Select
       Accept Read_Signal do
           -- KBD-signal read.
           Signal := GET_KBD_SIGNAL; -- Left as an exercise. (Get_Immidate?)
       End accept;
       Accept Read Direction( X : out Direction) do
         case Signal is
              When Up_Code => X:= Up;
              When Down_Code => X:= Down;
              When Left_Code => X:= Left;
              When Right_Code => X:= Right;
              When others => X:= None;
         end case;
       end accept;
    OR
       Accept Read_Signal;
       Finished:= True
    End select;
  End loop;
End Get_Input;

And you’d use the same structure to implement the reading for a game-pad.
Thus, your main game-code would have something like:
Controller : Get_Input'Class := Select_Control;
which would return the proper interface-device, and would present to the rest of your code a consistant method for interface.

Note: this is top-of-my-head/untested, but should be close to what you’ll want for an interchangeable input.

yes, this is a possible interface for handling input, but it just kicks the problem down the road.

Now Get_Input.Read_Signal likely contains the blocking call. I still don’t have a real mechanism (at least in pure ADA) to unblock that task to allow it to clean itself up.

And, if the Get_Immediate/Event_Device.Read isn’t blocking, then the interface requires polling.

Nah.
Just use a delay statement in the loop for the Get_Immidate.
This puts the problem to the tasking scheduler, and unless there’s no good timer-integration w/ the runtime (highly unlikely), it won’t use polling.

Text_IO is meant for formatted I/O, not for communication, not even for writing files. Things you want are done this way:

   task type Reader is
      entry Stop; -- You can ask me to quit
   end Reader;
   
   task body Reader is
      use GNAT.Serial_Communications;
      use Ada.Streams;
      Port   : Serial_Port;
      Buffer : Stream_Element_Array (1..1);
      Last   : Stream_Element_Offset;
   begin
      Open (Port, "/dev/tty"); -- Note interference with the standard input/output
      Set (Port, Block => False, Timeout => 1.0); -- No blocking, 1s timeout
      loop
         select
            accept Stop;
            exit;
         else
            Read (Port, Buffer, Last);
            if Last = 1 then
               Put_Line ("Input=" & Character'Val (Buffer (1)));
            end if;
         end select;
         delay 0.0; -- Yield the processor to anybody who wants it
      end loop;
      Close (Port);
      Put_Line ("Bye bye");
   exception
      when Error : others =>
         Put_Line ("Error:" & Exception_Information (Error));
   end Reader;

If you want any advanced OS I/O functionality, just call OS functions you need. E.g. under Windows you would call CancelIO on the file handle. Of course, the behaviour massively depends on the OS. There could be drivers which simply do not support immediate cancelation. It depends on the nature of the hardware.

You also can just call system functions like you do in C from Ada, e.g. epoll_wait

  type epoll_data is record -- Linux-specific stuff
      ptr : System.Address;
      fd  : Interfaces.C.int;
      u32 : Interfaces.Unsigned_32;
      u64 : Interfaces.Unsigned_64;
   end record with Convention => C;

   type epoll_event is record
      events : Interfaces.Unsigned_32; -- Epoll events
      data   : epoll_data;             -- User data variable
   end record with Convention => C;

   function epoll_wait
            (  epfd      : Interfaces.C.int;
               events    : epoll_event;
               maxevents : Interfaces.C.int;
               timeout   : Interfaces.C.int
            )  return Interfaces.C.int;
   pragma Import (C, epoll_wait);

It is not an Ada issue. The Ada standard library provides functionality that can be reasonably implemented on most OSes and bare bones, differently to the code you presented, which will not work, say, under Windows.

Yes. Delay can be 0.0 just to give breath to other tasks. It should cause rescheduling even if the time quant is not yet expired.
With Get_Immediate it would look like this:

  task type Reader is
      entry Stop;
   end Reader;
   
   task body Reader is
      C      : Character;
      Got_It : Boolean;
   begin
      loop
         select
            accept Stop;
            exit;
         else
            Get_Immediate (Standard_Input, C, Got_It);
            if Got_It then
               Put_Line ("Input=" & C);
            end if;
         end select;
         delay 0.0; -- Yield processor in case
      end loop;
      Put_Line ("Bye bye");
   exception
      when Error : others =>
         Put_Line ("Error:" & Exception_Information (Error));
   end Reader;

I think this is true for any language. Basically it boils down to if your IO driver at the OS level allows cancelling of blocked IO calls or not. If Get_Input.Read_Signal has a blocking call, then it is no longer the task that is blocking but the IO, so in order to cancel that, you need to cancel it at the IO level. For IO that don’t provide this mechanism, you’ll have to use some kind of polling. For terminal IO and similar situations I tend to go with something similar to Dmitry’s suggestion:

    type Event_Type is(Left, Right, Up, Down);
    
    task IO is
        entry Get(Event : out Event_Type);
        entry Stop;
    end IO;
    
    task body IO is
        Event_Ready : Boolean := False;
        Last_Event  : Event_Type := Left;
    begin
        while not Stop_All_Tasks loop
            select
                when Event_Ready => accept Get(Event : out Event_Type) do
                    Event := Last_Event;
                end Get;
                Event_Ready := False;
            or
                accept Stop;
                exit;
            or delay 0.0;
                -- Nonblocking code to get next event and set Event_Ready
            end select;
        end loop;
    exception
        when others => 
            Stop_All_Tasks := True;
            raise;
    end IO;

That allows me to have outside tasks block on this one using the Get entry which doesn’t progress until there is valid input to get (So outsides tasks will block at the task level on Get). It also allows a couple of ways to end the task. The Stop_All_Tasks boolean can be set to False to stop this (and presumably other) task or another thread can call IO.Stop. The nice thing here is that any other tasks blocking on Get will throw an exception once IO stops running, so it can be caught and cleanup can happen in other places.

If your IO is blocking AND your IO library provides a way to cancel the blocked IO, then you can replace the or delay 0.0; with an else and from the outside in other tasks you

  1. Set some flag to indicate not to do another blocking call
  2. Cancel the blocking call using your IO library method
  3. Call IO.Stop

Which I normally wrap into a procedure.

But either way, it all comes down to whether or not the IO driver/library has a way to cancel blocked IO or not, the language can’t force that. I think maybe C++ has similar situations (unless there is a new solution): c++ - How to reliably end a thread blocked on an IO task - Stack Overflow

I’m going to assume a protected object like

protected type Task_Control is
   function Time_To_Stop return Boolean;
   entry Wait_Until_Stop_Time;
   procedure Stop;
private -- Task_Control
   Stopping : Boolean := False;
end Task_Control;

This is useful for a lot of systems. There might be one object per task, or a single object for all tasks. The function can be used where polling is necessary; the entry when it’s not.

Conceptually, what you want the task to do is

loop
   select
      Control.Wait_Until_Stop_Time;
   then abort
      -- Blocking call to get Item
      Item_Sink.Put (Item => Item);
   end select;
end loop;

(Where Item_Sink is the first step in dealing with Item, often a protected/synchronized queue.)

If that works, then you’re done. If it doesn’t, then you’ll have to use polling. The first question is how often you need to poll. Even if the user is hitting the same key as fast as possible, the time between keystrokes will still be a Long Time for your computer. 0.1 seconds is probably a lower limit on the time between keystrokes, so using an interval of 0.05 seconds should be safe. (This assumes a non-blocking call to get an Item that returns immediately with a Boolean to indicate if an Item was obtained, similar to Get_Immediate.)

The second question is how often the task needs to check for termination. If the program keeps running for five seconds after the user has told it to quit then users will think something is wrong. People generally consider an interval of 0.2 seconds to be instantaneous, so the program shouldn’t take more than that to end. You don’t need to check for termination after every attempt to get a keystroke, just often enough to end within 0.2 seconds.

These considerations lead to

Next := Clock;
...
Until_Stop : loop
   exit Until_Stop when Control.Time_To_Stop;

   Check_Interval : for I in 1 .. 20 loop -- 0.2 seconds
      Next := Next + 0.05;
      -- Non-blocking call to get Item

      if Item_Obtained then
         Item_Sink.Put (Item => Item);
      end if;

      delay until Next;
   end loop Check_Interval;
end loop Until_Stop;

In the general case your non-blocking call may include a time-out parameter, in which case you don’t need the inner loop:

Until_Stop : loop
   exit Until_Stop when Control.Time_To_Stop;

   -- Non-blocking call to get Item with a time out of 0.2 seconds

   if not Timed_Out then
      Item_Sink.Put (Item => Item);
   end if;
end loop Until_Stop;

Jut want to clarify this since the original poster is newer to Ada: The -- Blocking call to get Item part needs to be something well defined in Ada. If your blocking call is a system level OS call that blocks it may not abort. See paragraphs 15-19 of section 9.8 of the RM for details: Abort of a Task - Abort of a Sequence of Statements

I know your suggestion of the protected/synchronized queue is the right answer here, but I didn’t want the oriiginal poster start thinking of just replacing that with the blocking IO call (unless it is one of the things listed of course).

What is wrong with Get_Immediate? There is enough queues between the serial line/emulator and the resulting character…

Thanks for all the input, I’ve gotten a lot of interesting things to play around with now, but I think the discussion has somewhat gone of the rails.

Fundamental Problem Statement

When doing development, my main task got an exception due to a development bug (skill issue, I know). Rather than crashing, the program just “froze” because other tasks were still running.

I wanted to know if there was a reasonable way to kick the other potentially blocked thread to tell it to exit so I can receive my CONSTRAINT_ERROR and line number so I can continue development.

It turns out the answer is largely no, unless you roll a fancy epoll/eventfd based solution.

Apparent Solutions

Potential Solution #1

  1. Write your own C binding around your blocking call that supports cancellation using an eventfd or something.
  2. always remember to catch exceptions at the top level (or install an specific termination handler)
  3. Iterate over all your potentially blocking descriptors (sockets etc.) and tell them all to cancel.
  4. Re-raise the exception or print the information in the Exception_Occurrence.

Potential Solution #2

Only block on objects that exist within the Ada language abstraction where you can provide your own reasonable timeouts and then wait patiently for all of them to expire to receive your CONSTRAINT_ERROR.
e.g.

select
    delay 2.0;
    -- Do something DRASTIC
then abort
    -- This better not call Ada.Text_IO.Get_Immediate(c) underneath
    -- or you'll still be stuck...
    SomeEntry.Call;
end select;

Don’t forget that all your server-y tasks selects need or terminate.
Also, don’t forget to have a global you can mark as “Exit now” that all your tasks will check periodically.

Potential Solution #3

Don’t use blocking APIs ever.

#1

  • Breaking blocking is ether possible or impossible regardless Ada or C. The normal implementation of Ada task is by an OS thread. So there is simply no any difference between Ada and C.
  • I have no idea why you want to re-raise an exception elsewhere and cannot print it from the task. In any case you can save exception occurrence and do whatever you want with it even re-raise it anywhere you wanted.
  • Blocking socket I/O is aborted by closing the socket. Do not forget to shut the socket down to avoid surprises. It is not recommended to use blocking socket I/O anyway. See socket select which can be cancelled any time.

#2 Never use asynchronous transfer of control except for aborting computations.

#3 If you want to use blocking API then usually there are options to set a reasonable timeout (e.g. 1s for serial I/O) or an event cancelling the I/O. If API blocks forever, maybe you should use a better one.

You still did not explain what was wrong with a non-blocking variant of Get_Immediate. Here is a complete program:

with Ada.Text_IO;     use Ada.Text_IO;
with Ada.Exceptions;  use Ada.Exceptions;

procedure Test is
   task type Reader is
      entry Stop;
   end Reader;
   
   task body Reader is
      C      : Character;
      Got_It : Boolean;
   begin
      Put_Line ("Hello, type something");
      loop
         select
            accept Stop;
            exit;
         else
            Get_Immediate (Standard_Input, C, Got_It);
            if Got_It then
               Put_Line ("Input=" & C);
            end if;
         end select;
         delay 0.0; -- Yield processor in case
      end loop;
      Put_Line ("Bye bye");
   exception
      when Error : others =>
         Put_Line ("Error:" & Exception_Information (Error));
   end Reader;
   
   Worker : Reader;
begin
   delay 3.0;
   Put_Line ("Time to rest");
   Worker.Stop;
end Test;   

This is by design: having a single task-error bring an entire program down rather than a subsystem is less robust. (I don’t know if there was any feedback from the DoD in design on this; but it makes sense if you think in terms of “Oh, the radar was shot off…” not crapping out the flight-control.)

The task-registration or polling solution is the only way to build such a dynamic system with scaling. Remember that, in Ada, you have a LOT of information from the runtime — typically in the form of attributes. Take a look at attributes related to tasks.

Why?
You don’t need C for anything you’ve said.

This is just good design practice.
If you have a lot of “shaped the same” subprograms, you can wrap the task in a generic and use formal parameters.

How else are you going to tell them to cancel?
I mean other than deferring program cleanup (including tasking and memory) to the OS.

I mean, how else are you going to do things?

Why have a global at all?
A registry-keeping polling task is much better suited: besides calling the termination entry, or forcing direct termination via the RTL’s tasking system, you can also build any logging that’s needed WRT tasking-level issues right there.

You can use blocking APIs… you just need to be aware of what you’re doing, and why… and consider the implications.

Remember: Ada is not C++.
While there’s a lot of code you can try to use as a template for Ada, it’s going to be far more pain to try to “translate” (read: write C++ in Ada) a C++ solution than it will to use Ada the way it was designed: to model the problem-space with the type-system. (This includes Tasks, there are subtilties that you have to be aware of when using them, but they are superbly suited for writing portable code: subsystems[-of-control], protocols, etc.)