Scheduling (Device Signalled)

Introduction

Unless interrupts are used, peripheral devices have to be polled to enquire their state, for example the readiness to receive more data, or the availability of a measurement from the controlled system (environment). Polling by busy-waiting in the control process itself is usually not applicable in a multi-process program.

Considering interrupt-driven designs, the RISC processor has exactly one interrupt input line. With more than one peripheral device, this would mean to wire all interrupt signals together, and distinguish the actually occurring interrupt in the handler software, for example by polling all relevant devices’ state via peripheral IO upon interrupt, or via an extended interrupt controller in the FPGA.

Please note that this shall in no way be read as argument against interrupt-driven designs in general. It’s an alternative approach, keeping strictly to the concept of cooperative scheduling. Real-time constraints can only be met if the timely handling of the device signals can be guaranteed with the overall process schedule – a basic principle of cooperative scheduling without interrupts.

Overview

The basic idea is to delegate the polling to the scheduler, but in a very efficient manner, making use of FPGA logic. As with process timing, the scheduler – ie. the Oberon Loop – only checks if the ready bit for a process is set, at a defined IO address. Note that the scheduling algorithm here does not use process priorities, as described here.

Oberon.Loop is extended accordingly:

MODULE Oberon;

  (* ... *)

  VAR cp: Process; (* the current process, in a linked ring of processes *)

  PROCEDURE Loop;
  BEGIN
    IF Console.Available() THEN
      (* command and upload handling *)
    ELSE
      IF cp # NIL THEN
        cp := cp.next;
        IF ProcDevSig.ProcessReady(cp.pcNo) THEN  (* device signal handling *)
          ProcDevSig.ResetSignals(cp.pcNo);
          cp.state := Active;
          Coroutines.Transfer(loop, cp.cor) 
        ELSIF ProcTimers.ProcessReady(cp.pcNo) THEN   (* process timing *)
          ProcTimers.SetPeriod(cp.pcNo, cp.period);
          IF cp.state # Suspended THEN
            cp.state := Active;
            Coroutines.Transfer(loop, cp.cor)
          END
        END
      END
    END
  END Loop;

  (* ... *)

END Oberon.

ProcDevSig.mod

ProcDevSig.mod provides the following API to control the FPGA-based controller.

MODULE ProcDevSig;
  IMPORT SYSTEM;

  CONST
    DevSigAdr = -144; (* write awaited device signal *)
    PrReadyAdr = DevSigAdr;   (* read process ready *)
    ProcNumShift = 27;

  PROCEDURE* SetSignal*(pn: INTEGER; devSig: INTEGER);
  BEGIN
    SYSTEM.PUT(DevSigAdr, LSL(pn, ProcNumShift) + LSL(1, devSig))
  END SetSignal;

  PROCEDURE* ResetSignals*(pn: INTEGER);
    SYSTEM.PUT(DevSigAdr, LSL(pn, ProcNumShift))
  END ResetSignals;

  PROCEDURE* ProcessReady*(pn: INTEGER): BOOLEAN;
    RETURN SYSTEM.BIT(PrReadyAdr, pn)
  END ProcessReady;

END ProcDevSig.

As with the process timers, each process has its own device signal controller. The current FPGA design allows for up to 32 processes.

The IO address for each controller is the same, the number of the addressed timer is transmitted as bits [31:27] with the corresponding data, ie. the signal number (as bit). Obviously, this limits the number of possible device signals to 27.

Device Timeout

Peripheral devices can fail to respond, hence we need a timeout, else a process might await a device signal forever. Waiting “forever” must be allowed as well, though, for example with an RS232 device listening to an input terminal.

Await Device Signal Machinery

Below the procedure in Oberon.mod, to be called from a process, to await a specific device signal. Device signals are numbered, according to their wiring in the FPGA. A module DevSignals.mod represents that wiring in Oberon code.

MODULE Oberon;

  PROCEDURE AwaitDevSig(devSig: INTEGER; timeout: INTEGER; VAR res: INTEGER);
  BEGIN
    ASSERT(timeout >= 0);
    ProcDevSig.SetSignal(cp.cpNo, devSig);
    IF timeout = 0 THEN   (* no timeout requested, ie. wait forever *)
      cp.state := AwaitDevSig
    ELSE
      ProcTimers.SetDelay(cp.cpNo);   (* use process timers for timeout *)
      cp.state := AwaitDevSigTo
    END;
    Coroutines.Transfer(cp.cor, loop);
    res := cp.retVal (* see below *)
  END AwaitDevSig;

END Oberon.

Oberon.Loop With Device Timeout

Here’s the extended Oberon.Loop, handling process timing, awaiting device signals, and device signal timeouts.

MODULE Oberon;

  PROCEDURE Loop;
  BEGIN
    IF Console.Available() THEN
      (* command and upload handling *)
    ELSE
      IF cp # NIL THEN
        cp := cp.next;
        IF ProcDevSig.ProcessReady(cp.pcNo) THEN
          ProcDevSig.ResetSignals(cp.pcNo);
          IF cp.state = AwaitDevSigTo THEN
            ProcTimers.CancelDelay(cp.pcNo)
          END;
          cp.state := Active;
          cp.retVal := OK;
          Coroutines.Transfer(loop, cp.cor)
        ELSIF ProcTimers.ProcessReady(cp.pcNo) THEN
          ProcTimers.SetPeriod(cp.pcNo, cp.period);
          cp.retValue := OK;
          IF cp.state = AwaitDevSigTo THEN
            ProcDevSig.ResetSignals(cp.pcNo);
            cp.retVal := Timeout
          END;
          IF cp.state IN -{Suspended, AwaitDevSig} THEN
            cp.state := Active;
            Coroutines.Transfer(loop, cp.cor)
          END
        END
      END
    END
  END Loop;

END Oberon.

As described here, delays take precedence over period timing, hence we know a process awaiting a signal got a timeout when entering the ELSIF branch.

The process TYPE has an additional field, retValue, to allow to report back the outcome of awaiting a device signal, namely signal received or timeout. The return value is an integer, with OK = 0.

RS232 Driver

We now can write an RS232 driver making use of device signals, for example for an FGPA-buffered RS232 device.

MODULE RS232b;

  IMPORT SYSTEM, Oberon, RS232dev, Out;

  CONST
    TxFull = RS232dev.TXBF;   (* transmit buffer full *)
    OK = 0; (* no error *)

  PROCEDURE PutChars*(dev :RS232dev.Device; data: ARRAY OF CHAR; n: INTEGER; VAR res: INTEGER);
    VAR cnt: INTEGER;
  BEGIN
    cnt := 0;
    WHILE cnt < n DO
      Out.String(">>"); Out.Ln; (* not part of the driver, just for the test below *)
      WHILE (cnt < n) & ~SYSTEM.BIT(dev.statusAdr, TxFull) DO
        SYSTEM.PUT(dev.dataAdr, ORD(data[cnt]));
        INC(cnt)
      END;
      IF cnt < n THEN
        Oberon.AwaitDevSig(dev.txSig, dev.txTimeout, res);
        IF res # OK THEN cnt := n END
      END
    END
  END PutChars;

  (* ... *)

END RS232b.

This driver uses the device type in module RS232dev.mod, which forms the configuration layer for all RS232 devices instantiated in the FPGA. See below how it is instantiated and initialised, including the device signals.

MODULE RS232dev;

  TYPE
    Device* = POINTER TO DeviceDesc;
    DeviceDesc* = RECORD(Texts.TextDeviceDesc)
      dataAdr*, statusAdr*: INTEGER;
      txTimeout*, rxTimeout*: INTEGER;
      txSig*, rxSig*: INTEGER
    END;

END RS232dev.

The timeouts can be set to different values for transmit and receive, but are assumed to be the same for all uses of this specific device. This is less flexible than a specific per-use timeout, but keeps the API to the device driver narrower from the process programmer’s point of view, and the timeout is consistent and easy to change. A design decision that might need to be reconsidered, if only for specific application cases.

Demo

The following small test program demonstrates the use and effect of the device signal equipped RS232 device. The transmit buffer of the selected device RS232dev.Dev3 holds 31 characters, the receive buffer 15 characters.

MODULE TestProcessIO;

  IMPORT Oberon, DevSignals, RS232dev, RS232 := RS232p, Out;
  
  CONST
    TxTimeout = 10;
    RxTimeout = 0;    (* no timeout *)
  
  VAR
    p1, p2, p3: Oberon.Process;
    s1, s2, s3: ARRAY 1024 OF BYTE;
    dev: RS232dev.Device;
    data1: ARRAY 128 OF CHAR;
    data2: ARRAY 8 OF CHAR;
    i: INTEGER;
    
  PROCEDURE p1c;
    CONST NumChars = 128;
    VAR res: INTEGER;
  BEGIN
    REPEAT
      Out.String("p1--"); Out.Ln;
      RS232.PutChars(dev, data1, NumChars, res);
      ASSERT(res = 0);
      Out.String("p1--"); Out.Ln;
      Oberon.NextProc
    UNTIL FALSE
  END p1c;
  
  PROCEDURE p2c;
    CONST NumChars = 4;
    VAR res: INTEGER;
  BEGIN
    REPEAT
      RS232.GetChars(dev, data2, NumChars, res);
      data2[NumChars] := 0X;
      Out.String(data2); Out.Ln;
      Oberon.NextProc
    UNTIL FALSE
  END p2c;
  
  PROCEDURE p3c;
  BEGIN
    REPEAT
      Out.String("p3"); Out.Ln;
      Oberon.NextProc
    UNTIL FALSE
  END p3c;
   
  PROCEDURE Run1*;
  BEGIN
    Oberon.InstallProc(p1);
    Oberon.InstallProc(p3)
  END Run1;
  
  PROCEDURE Run2*;
  BEGIN
    Oberon.InstallProc(p1);
    Oberon.InstallProc(p2)
  END Run2;
  
  PROCEDURE Stop*;
  BEGIN
    Oberon.RemoveProc(p1);
    Oberon.RemoveProc(p2);
    Oberon.RemoveProc(p3)
  END Stop; 
  
BEGIN
  NEW(dev); RS232dev.Init(dev, RS232dev.Dev3);
  RS232dev.SetDevSignals(dev, DevSignals.RS232dev3TxBufEmpty, DevSignals.RS232dev3RxBufNonEmpty, TxTimeout, RxTimeout);
  NEW(p1); Oberon.InitProc(p1, p1c, s1, 1000, 0);
  NEW(p2); Oberon.InitProc(p2, p2c, s2, 1000, 0);
  NEW(p3); Oberon.InitProc(p3, p3c, s3, 5, 0);
  FOR i := 0 TO 127 DO
    data1[i] := CHR((i MOD 10) + ORD("1"))
  END
END TestProcessIO.

Process p1 simply repeatedly outputs 128 characters to RS232dev.Dev3, which is connected to another serial terminal than the Astrobe console. p2 repeatedly reads four characters from RS232dev.Dev3, and prints them to the Astrobe console. p3 serves as “sentinel” process to check if it actually gets scheduled while the other processes are awaiting the device signals.

Run1

When we execute Run1, we get in the Astrobe terminal:

p3
p1--
>>
>>
p3
>>
>>
p1--
p3

The temporary test code in the RS232 driver prints “»” when p1 starts to fill the buffer in the FPGA, and the RS232 device starts to transmit concurrently. Because p1 prints 128 characters, and we have a 31 character transmit buffer, p3 can sneak in its output while p1 awaits the second TxEmpty device signal. p3 runs with a period of 5 milliseconds. Note that p1 can transmit 32 characters per RS232.PutChars call, because the first character in the buffer will have been consumed by the RS232 device when the process has finished putting 31 characters into the buffer, allowing one more.

Run2

When we execute Run2, and enter, say “1234” into RS232dev.Dev3, we simply see p2 printing these characters in the Astrobe terminal, as soon as all four requested characters have been entered, all while p1 does its output thing in parallel. Note that the RS232 driver could easily be modified to define and implement other conditions to return the read chars, such as CR entered to read a full line of input, without the need to poll the device for each single character.

Timeouts

The timeout for reading from RS232dev.Dev3 is set to RxTimeout = 0, that is, the timeout feature is disabled, and the process waits forever until the requested four characters are read.

The timeout for writing to the terminal is set to TxTimeout = 10 milliseconds, ie. above what is required to write 31 characters at 115,200 Baud (2.7 ms). If we lower this timeout to 2 milliseconds we get the trap caused by the violation of the ASSERT statement in p1, as expected. Handling the timeout with an ASSERT is just used as simple example here. p1 could also retry, or pursue other recovering strategies.