ssm-lang / Scoria

This is an embedding of the Sparse Synchronous Model, in Haskell!
BSD 3-Clause "New" or "Revised" License
4 stars 0 forks source link

Derived combinators to sell EDSLs in the paper #19

Open Rewbert opened 3 years ago

Rewbert commented 3 years ago

With an EDSL, implementing derived combinators from the primitives becomes very easy. If we can think of some nice derived operators to showcase in the August paper, that would be nice. The first candidate (stolen from Stephens paper) is the waitAll combinator. wait waits for any of the references to be written to, while waitAll will wait for all of them to be written at least once.

-- | Wait for all the references to be written to
waitAll :: [Ref a] -> SSM ()
waitAll refs = fork $ map waitSingle refs
  where
      waitSingle :: Ref a -> SSM ()
      waitSingle = box "waitSingle" ["r"] $ \r -> wait [r]

Another simple combinators is a simple delay, which behaves similarly to a conventional sleep function.

-- | Delays the current process for t 'ticks', essentially the same as sleep
-- for conventional threads.
delay :: Exp Word64 -> SSM ()
delay t = fork [delayprocess t]
  where
      delayprocess :: Exp Word64 -> SSM ()
      delayprocess = box "delay" ["time"] $ \time -> do
          r <- var false'
          after time r true'
          wait [r]

Another pattern that I think might be useful to make a combinator for is that of alternating a reference between two values (e.g blinking a led with a set interval).

-- | Alternates between two values on a reference
alternate :: Ref a -> Exp a -> Exp a -> Exp Word64 -> SSM ()
alternate = fork [ alternateprocess r v1 v2 time ]
  where
        alternateprocess :: Ref a -> Exp a -> Exp a -> Exp Word64 -> SSM ()
         alternateprocess = box "alternate" ["r","v1","v2","time"] $ \r v1 v2 time -> do
               while' true' $ do
                   delay time
                   r <~ v1
                   delay time
                   r <~ v2

This can naturally be generalized to a more general cycle primitive which does the same but for a sequence of values. We can not implement this yet, as we need to add support for lists to do that.

-- | Given a reference and a set of values, and a delay, cycle through the
-- values at the given interval. Starts all over when reached the end of the
-- list of values.
cycle :: Ref a -> [Exp a] -> Exp Word64 -> SSM ()
cycle = undefined

With this, alternate in turn just becomes a specific case of cycle.

alternate :: Ref a -> Exp a -> Exp a -> Exp Word64 -> SSM ()
alternate r v1 v2 t = cycle r [v1,v2] t

Now we see another pattern that we could perhaps abstract away (but that would be mainly for our own sake, not for the end programmer). These derived combinators all define some procedure that does the work and issues a fork call to that procedure. I am not sure how to generalize it right now, since we pass in the procedure & parameter names, but maybe it's something we can look at in the future.

@j-hui mentioned a combinator that would make allocation and deallocation of a resource explicit. The idea is that we want to fork a process that allocates some resource, passes that resource to additional processes that operate on them, and then deallocates the resource. Very similar to these C patterns:

void f() {
  char buffer[64];
  doSomethingWithBuffer(buffer);
  return;
}

void g() {
  int fd = open(...);
  foo(fd);
  close(fd);
}

I don't think we can derive such a combinator right now, but it's interesting to look at. It would surely be a very handy combinator for handling memory resources etc when we are developing IoT applications. I sketched this rough code up yesterday:

-- | If we can somehow create and destroy a value, maybe it can look
-- like this? If `create` does anything special that needs a nice
-- teardown, that work can be done by `destroy`.
class SSMType a => Resource a where
    create  :: proxy a -> SSM (Ref a)
    destroy :: Ref a   -> SSM ()

-- | Simple dummy-instance for int, which is not so exciting. Perhaps
-- a more interesting example could be opening/closing a file instead.
instance Resource Int32 where
    create _  = var 0
    destroy r = return ()

-- | Need to use forall a to make the a in `superviseprocess` the same as
-- the a in supervise.
supervise :: forall a . Resource a => [(Ref a -> SSM ())] -> SSM ()
supervise procs = fork [ superviseprocess procs ]
  where
      -- | We can not generate code for this procedure yet. What type is
      -- the `a`?
      superviseprocess :: [(Ref a -> SSM ())] -> SSM ()
      superviseprocess procs = boxNullary "superviseprocess" $ do
          -- allocate the resource
          v <- create $ Proxy @a
          -- hand the resource over to the other processes
          fork $ map ($ v) procs
          -- release the resource
          destroy v

As my comment says, it's not possible to generate code for superviseprocess yet. Not sure what the best way to go around this is. Specialization? @koengit ?

Rewbert commented 3 years ago

The only one of these that we can generate code for right now is delay, the rest are not possible since we can not generate code for polymorphic functions (yet).

j-hui commented 2 years ago

This is a really simple combinator, but it would be nice to have an infinite loop combinator

loop :: SSM () -> SSM ()
loop = while' true'

would also be great to have a do-while loop kind of construct:

doWhile :: Exp Bool -> SSM () -> SSM ()
doWhile c b = b >> while' c b

note that doWhile c b isn't very structurally evocative, unlike C's do { b } while (c) , so we might want to rename that.

until is another good one to have:

until :: Exp Bool -> SSM () -> SSM ()
until c = while $ not c

All basic sugar, but nice to have when writing programs.

j-hui commented 2 years ago

One-shot and its variations:

Basic one-shot:

oneShot :: SSMTime -> Bool -> Ref () -> Ref Bool -> SSM ()
oneShot delay low i o = while True $ do
  wait [i]
  o <~ not low
  after delay, o <~ low

A more type-generic version that acts more like a functor, mapping over values of the input reference:

oneShotMap :: SSMTime -> Exp b -> (Exp a -> Exp b) -> Ref a -> Ref b -> SSM ()
oneShotMap delay low f i o = while True $ do
  wait [i]
  o <~ f (deref i)
  after delay, o <~ low

We can redefine oneShot using oneShotMap:

oneShot delay low = oneShotMap delay low (const $ not low)

For the following variations, I'll use the type-specific version for brevity.

The above implementation will issue an additional instantaneous assignment if it receives two consecutive input signals before it is able to reset the output signal. While the additional assignment may seem redundant, it has the effect of waking up waiting processes (though with no change in value). That may or may not be desirable. This implementation ensures that only alternating assignments are made:

oneShot' :: SSMTime -> Exp Bool -> Ref () -> Ref Bool -> SSM ()
oneShot' delay low i o = while True $ do
  wait [i]
  when (deref o != low) $ o <~ not low
  after delay, o <~ low -- extends scheduled shut-off time

Note that if the scheduled o <~ low update takes place at the exact same time that input is received on i, o will be assigned to twice in the same instant, with different values.


Meahwhile, if we wanted to imitate the behavior of the one-shot circuit shown here, we need to make a few changes. First, the input needs to be a Ref Bool as well, to remain faithful to the circuit analogy. We only respond to rising edges. We also need to ignore repeated assignments of the same value. Secondly, we need to make sure that once we've received a rising edge input, we ignore subsequent input until we've written low value.

oneShotW :: SSMTime -> Exp Bool -> Ref Bool -> Ref Bool -> SSM ()
oneShotW delay low i o = while True $ do
  -- wait until i <~ true
  while True $ do
    wait [i]
    when (deref i) $ break

  -- raise o
  o <~ not low

  -- set alarm
  wake <- var ()
  after delay, wake <~ ()
  wait [wake]

  -- reset o
  o <~ low

Note that here we use an internal alarm rather than waiting on o, because we can't assume we are the only process writing to o. This inadvertently solves another issue: in the previous examples, we mixed instananeous assignments with delayed assignments to o, such that all processes would see the delayed o <~ low assignment, but only processes of lower priority would see the instananeous o <~ not low assignment, creating an odd asymmetry that leads to unexpected behavior. For instance, if o is an output LED with a higher priorirty output handler, the output handler would never turn on the LED, but will receive low signals to o that could clobber other concurrent signals.

The implementation of oneShotW is such that we only ever use instanenous assignment on o, so that only lower priority processes will be able to see writes by oneShotW to o. A high priority output handler still wouldn't be able to receive output to the LED, but at least the output handler is uniformly deaf to both o <~ not low and o <~ low.


The fact that oneShotW uses instantaneous assignment precludes the use of high priority output handlers for o that can only evaluate delayed updates. We can adjust the implementations of oneShotW and oneShot' to only use delayed assignment, parametrized by some small latency that is used in place of the instananeous assignment:

oneShotW_ :: SSMTime -> SSMTime -> Exp Bool -> Ref Bool -> Ref Bool -> SSM ()
oneShotW_ latency delay low i o = while True $ do
  -- wait until i <~ true
  while True $ do
    wait [i]
    when (deref i) $ break

  -- raise o
  after latency, o <~ not low

  -- set alarm
  wake <- var ()
  after delay, wake <~ ()
  wait [wake]

  -- reset o
  after latency, o <~ low

oneShot'_ :: SSMTime -> SSMTime -> Exp Bool -> Ref () -> Ref Bool -> SSM ()
oneShot'_ latency delay low i o = while True $ do
  wait [i]
  when (deref o != low) $ after latency, o <~ not low
  after (latency + delay), o <~ low

We have a number of interesting combinators that we can extract from this example.

This one translates instantaneous assignments to one variable to delayed assignments on another. When scheduled as a low priority process, this can be used to forward instananeous assignments to high priority output handlers:

latency :: SSMTime -> Ref a -> Ref a -> SSM ()
latency d i o = while True $ do
  wait [i]
  after d, o <~ deref i

The idea is that latency introduces a short but necessarily and predictable amount of latency to enable high priority output handlers.

This implementation assumes that i != o. If the are the same, this implementation will misbehave terribly, spamming the system with writes due to a feedback loop.

With the current runtime system, there isn't a way to distinguish between an instantaneous and delayed assignment. Having such a feature may be useful for writing low-priority processes that convert only instantaneous assignments into delayed assignments, i.e., mimicking a default delay.


From oneShotW, we can extract a waitUntil combinator:

waitUntil :: [Ref a] -> SSMExp Bool -> SSM ()
waitUntil refs cond = while True $ wait refs >> when cond break
Rewbert commented 2 years ago

"The fact that oneShotW uses instantaneous assignment precludes the use of high priority output handlers for o that can only evaluate delayed updates. We can adjust the implementations of oneShotW and oneShot' to only use delayed assignment, parametrized by some small latency that is used in place of the instananeous assignment"

This sounds like a really good place for adding perhaps a new primitive RTS function. Immediate assignment which wakes up everyone. This primitive would be available only to us as compiler developers, and not exposed to programmers. Or perhaps it could be, but very well documented and with a name like pleaseDoNotUseImmediateAssignment, similar to stuff like unutterablyUnsafePerformIO and so on.

Things like the latency operator, if you call it just like that, it's going to make your program halt there forever, right? It sounds like a good combinator but we need to think of a nice way of using it.