Netwire

From HaskellWiki
Revision as of 19:54, 6 August 2011 by Ertes (talk | contribs) (Hackage link)
Jump to navigation Jump to search

Netwire is a library for functional reactive programming, which uses the concept of arrows for modelling an embedded domain-specific language. This language lets you express reactive systems, which means systems that change over time. It shares the basic concept with Yampa and its fork Animas, but it is itself not a fork.

Download netwire


Features

Here is a list of some of the features of netwire:

  • arrowized interface,
  • applicative interface,
  • signal inhibition (ArrowZero / Alternative),
  • choice and combination (ArrowPlus / Alternative),
  • self-adjusting wires (ArrowChoice),
  • rich set of event wires,
  • signal analysis wires (average, peak, etc.),
  • impure wires.

Quickstart

This is a quickstart introduction to Netwire for Haskell programmers familiar with arrowized functional reactive programming (AFRP), for example Yampa or Animas. It should quickly give you an idea of how the library works and how it differs from the two mentioned.

The wire

Netwire calls its signal transformation functions wires. You can think of a wire as a device with an input line and an output line. The difference between a function and a wire is that a wire can change itself throughout its lifetime. This is the basic idea of arrowized FRP. It gives you time-dependent values.

A wire is parameterized over its input and output types:

data Wire a b


Differences from Yampa

If you are not familiar with Yampa or Animas, you can safely skip this section.

The main difference between Yampa and Netwire is that the underlying arrow is impure. While you can choose not to use the impure wires inside of the FRP.NetWire.IO module, it is a design choice for this library to explicitly allow impure computations. One theoretical implication is that you need to differentiate between pure stateless, pure stateful and impure signal transformations.

A concept not found in Yampa is signal inhibition. A wire can choose not to return anything. This way you can temporarily block entire subnetworks. This is most useful with the combination operator <+>. Example:

w = w1 <+> w2

The w wire runs its signal through the wire w1, and if it inhibits, it passes the signal to w2.

Another concept not found in Yampa is choice. Through the ArrowChoice instance wires allow you to choose one of a set of subwires for its signal without needing a switch. Essentially you can write if and case constructs inside of arrow notation.

Because of their impurity wires do not have an ArrowLoop instance. It is possible to write one, but it will diverge most of the time, rendering it useless.


Using a wire

To run a wire you will need to use the withWire and stepWire functions. The withWire initializes a wire and gives you a Session value. As metioned earlier in general a wire is a function, which can mutate itself over time. The session value captures the current state of the wire.

initWire :: Wire a b -> (Session a b -> IO c) -> IO c
stepWire :: a -> Session a b -> IO (Maybe b)

The stepWire function passes the given input value through the wire. If you use stepWire, then the wire will mutate in real time. If you need a different rate of time, you can use stepWireDelta or stepWireTime instead.

The stepping functions return a Maybe b. If the wire inhibits, then the result is Nothing, otherwise it will be Just the output. Here is a complete example:

{-# LANGUAGE Arrows #-}

module Main where

import Control.Monad
import FRP.NetWire
import Text.Printf


myWire :: Wire () String
myWire =
    proc _ -> do
        t <- time -< ()
        fps <- avgFps 1000 -< ()
        fpsPeak <- highPeak -< fps

        if t < 4
          then identity -< "Waiting four seconds."
          else identity -<
                   printf "Got them! (%8.0f FPS, peak: %8.0f)"
                          fps fpsPeak


main :: IO ()
main = withWire myWire loop
    where
    loop :: Session () String -> IO ()
    loop session =
        forever $ do
            mResult <- stepWire () session
            case mResult of
              Nothing -> putStr "Signal inhibted."
              Just x  -> putStr x
            putChar '\r'

This program should display the string "Waiting four seconds." for four seconds and then switch to a string, which displays the current average frames per second and peak frames per second.

Note: Sessions are thread-safe. You are allowed to use the stepping functions for the same wire from multiple threads. This makes it easy to implement conditional stepping based on system events.


Writing a wire

Time

To use this library you need to understand the concept of time very well. Netwire has a continuous time model, which means that when you write your applications you disregard the discrete steps, in which your wire is executed.

Technically at each execution instant (i.e. each time you run stepWire or one of the other stepping functions) the wire is fed with the input as well as a time delta, which is the time passed since the last instant. Hence wires do not by themselves keep track of what time it is, since most applications don't need that anyway. If you need a clock, you can use the predefined time wire, which will be explained later.

Wires have a local time, which can be different from the global time. This can happen, when a wire is not actually run, because an earlier wire inhibited the signal. It also happens, when you use choice. For example you can easily write a gateway, which repeatedly runs one wire the one second and another wire the other second. While one wire is run, the other wire is suspended, including its local time.

Local time is a switching effect, which is especially visible, when you use the switching combinators from FRP.NetWire.Switch. Local time starts when switching in.

Pure stateless wires

Pure stateless wires are easy to explain, so let's start with them. A pure stateless wire is essentially just a function of input. The simplest wire is the identity wire. It just returns its input verbatim:

identity :: Wire a a

If you run such a wire (see the previous section), then you will just get your input back all the time. Another simple wire is the constant wire, which also disregards time:

constant :: b -> Wire a b

If you run the wire constant 15, you will get as output the number 15 all the time, regardless of the current time and the input.

Note: You can express identity as arr id, but you should prefer identity, because it's faster. Likewise you can express constant x as arr (const x), but again you should prefer constant.

Pure stateful wires

Let's see a slightly more interesting wire. The time wire will return the current local time. What local means in this context was explained earlier.

time :: Wire a Double

As the type suggests, time is measured in seconds and represented as a Double. The local time starts from 0 at the point, where the wire starts to run. There is also a wire, which counts time from a different origin:

timeFrom :: Double -> Wire a Double

The difference between these stateful and the stateless wires from the previous section is that stateful wires mutate themselves over time. The timeFrom x wire calculates the current time as x plus the current time delta. Let's say that sum is y. It then mutates into the wire timeFrom y. As you can see there is no internal clock. It is really this self-mutation, which gives you a clock.

TODO: More to come.