Difference between revisions of "Netwire"

From HaskellWiki
Jump to navigation Jump to search
(Incompatibility notice.)
(Update to 1.2.6)
Line 2: Line 2:
   
 
:[http://hackage.haskell.org/package/netwire Download netwire]
 
:[http://hackage.haskell.org/package/netwire Download netwire]
 
'''WARNING''': This wiki page corresponds to netwire version 1.0.0. The new version contains incompatible changes. I will update this page as soon as I have some spare time.
 
 
   
 
== Features ==
 
== Features ==
Line 27: Line 24:
 
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.
 
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:
+
A wire is parameterized over an underlying monad and its input and output types:
   
 
<haskell>
 
<haskell>
data Wire a b
+
data Wire m a b
 
</haskell>
 
</haskell>
   
Line 55: Line 52:
 
=== Using a wire ===
 
=== 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.
+
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 mentioned earlier in general a wire is a function, which can mutate itself over time. The session value captures the current state of the wire.
   
 
<haskell>
 
<haskell>
withWire :: Wire a b -> (Session a b -> IO c) -> IO c
+
withWire :: (MonadIO m, MonadIO sm) => Wire m a b -> (Session m a b -> sm c) -> sm c
stepWire :: a -> Session a b -> IO (Maybe b)
+
stepWire :: MonadIO m => a -> Session m a b -> m (Output b)
 
</haskell>
 
</haskell>
   
Line 65: Line 62:
   
 
<haskell>
 
<haskell>
stepWireDelta :: NominalDiffTime -> a -> Session a b -> IO (Maybe b)
+
stepWireDelta :: MonadIO m => NominalDiffTime -> a -> Session m a b -> m (Output b)
stepWireTime :: UTCTime -> a -> Session a b -> IO (Maybe b)
+
stepWireTime :: MonadIO m => UTCTime -> a -> Session m a b -> m (Output b)
 
</haskell>
 
</haskell>
   
 
Note that it is allowed to give zero or negative deltas and times, which are earlier than the last time. This lets you run the system backwards in time. If you do that, your wire should be prepared to handle it properly.
 
Note that it is allowed to give zero or negative deltas and times, which are earlier than the last time. This lets you run the system backwards in time. If you do that, your wire should be prepared to handle it properly.
   
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:
+
The stepping functions return a ''Output b'', which is just an alias for ''Either SomeException b'':
  +
 
<haskell>
  +
type Output = Either SomeException
 
</haskell>
  +
  +
If the wire inhibits (which is analogous to raising an exception), then the result is ''Left SomeException'', otherwise it will be ''Right b'', with ''b'' being the output. Here is a complete example:
   
 
<haskell>
 
<haskell>
Line 83: Line 86:
   
   
myWire :: Wire () String
+
myWire :: Wire IO () String
 
myWire =
 
myWire =
 
proc _ -> do
 
proc _ -> do
Line 100: Line 103:
 
main = withWire myWire loop
 
main = withWire myWire loop
 
where
 
where
loop :: Session () String -> IO ()
+
loop :: Session IO () String -> IO ()
 
loop session =
 
loop session =
 
forever $ do
 
forever $ do
mResult <- stepWire () session
+
output <- stepWire () session
case mResult of
+
case output of
Nothing -> putStr "Signal inhibted."
+
Left e -> print e
Just x -> putStr x
+
Right x -> putStrLn x
putChar '\r'
 
 
</haskell>
 
</haskell>
   
Line 113: Line 115:
   
 
Note: Sessions are thread-safe. You are allowed to use the stepping functions for the same session from multiple threads. This makes it easy to implement conditional stepping based on system events.
 
Note: Sessions are thread-safe. You are allowed to use the stepping functions for the same session from multiple threads. This makes it easy to implement conditional stepping based on system events.
  +
  +
Note: The type signatures of all Wires have an implicit ''Monad'' constraint on its first parameter. This constraint has been omit for the sake of brevity.
  +
 
== Signal inhibition ==
  +
 
A wire may choose not to return anything, at which point it is said to be inhibiting. If the whole wire network inhibits, then the stepping functions will return ''Left e'', where ''e :: SomeException''. Otherwise, a ''Right'' value is returned. If a wire in a sequence of wires inhibits, the later wires are not run.
   
 
== Writing a wire ==
 
== Writing a wire ==
Line 128: Line 136:
 
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.
 
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.
   
Time is measured in ''Double'' in Netwire. To improve type signatures there are two type aliases defined for you:
+
Time is measured in ''Double'' in Netwire. To improve type signatures there is a type aliases defined for you:
   
 
<haskell>
 
<haskell>
type DTime = Double
 
 
type Time = Double
 
type Time = Double
 
</haskell>
 
</haskell>
   
While ''Time'' refers to time, ''DTime'' refers to time deltas, i.e. time differences.
+
''Time'' is used to refer to local time and time deltas, i.e. time differences. It is represented in seconds.
   
 
=== Pure stateless wires ===
 
=== Pure stateless wires ===
Line 142: Line 149:
   
 
<haskell>
 
<haskell>
identity :: Wire a a
+
identity :: Wire m a a
 
</haskell>
 
</haskell>
   
Line 148: Line 155:
   
 
<haskell>
 
<haskell>
constant :: b -> Wire a b
+
constant :: b -> Wire m a b
 
</haskell>
 
</haskell>
   
Line 160: Line 167:
   
 
<haskell>
 
<haskell>
time :: Wire a Double
+
time :: Wire m a Time
 
</haskell>
 
</haskell>
   
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:
+
As the type suggests, time is measured in seconds and represented as a ''Time''. 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:
   
 
<haskell>
 
<haskell>
timeFrom :: Double -> Wire a Double
+
timeFrom :: Time -> Wire a Time
 
</haskell>
 
</haskell>
   
Line 176: Line 183:
   
 
<haskell>
 
<haskell>
integral :: Double -> Wire Double Double
+
integral :: Double -> Wire m Double Double
 
</haskell>
 
</haskell>
   
Line 182: Line 189:
   
 
<haskell>
 
<haskell>
slowClock :: Wire a Double
+
slowClock :: Wire m a Double
 
slowClock = proc _ -> integral 0 -< 0.5
 
slowClock = proc _ -> integral 0 -< 0.5
 
</haskell>
 
</haskell>
Line 189: Line 196:
   
 
<haskell>
 
<haskell>
particle :: Wire a Double
+
particle :: Monad m => Wire m a Double
 
particle =
 
particle =
 
proc _ -> do
 
proc _ -> do
Line 202: Line 209:
 
<haskell>
 
<haskell>
 
integral ::
 
integral ::
(NFData v, VectorSpace v, Scalar v ~ Double) =>
+
(Monad m, NFData v, VectorSpace v, Scalar v ~ Double) =>
v -> Wire v v
+
v -> Wire m v v
 
</haskell>
 
</haskell>
   
Line 209: Line 216:
   
 
<haskell>
 
<haskell>
particle2D :: Wire a (Double, Double)
+
particle2D :: Monad m => Wire m a (Double, Double)
 
particle2D =
 
particle2D =
 
proc _ -> do
 
proc _ -> do
Line 219: Line 226:
   
 
<haskell>
 
<haskell>
derivative :: Wire Double Double
+
derivative :: Wire m Double Double
derivativeFrom :: Double -> Wire Double Double
+
derivativeFrom :: Double -> Wire m Double Double
 
</haskell>
 
</haskell>
   
Line 229: Line 236:
 
=== Events ===
 
=== Events ===
   
Events are a useful tool to add discrete values to the system. As the name states an event usually denotes some condition or external event, which can be present at some instants and absent at others. A common use case for events is user input.
+
Events are a useful tool to add discrete values to the system. As the name states an event usually denotes some condition or external event, which can be present at some instants and absent at others. A common use case for events is user input. Events are wires that run if the event that it models has occurred and inhibit if otherwise.
 
Technically events are nothing special. Since they simply denote values, which can be absent, they are simply ''Maybe'' values. Netwire defines a type alias ''Event'' to enable you to be more specific in your type signatures:
 
 
<haskell>
 
type Event = Maybe
 
</haskell>
 
   
 
There is a large number of event wires in the '''FRP.NetWire.Event''' module. I will give you examples for some of the common ones here. It is worthwhile to have a look at the aforementioned module.
 
There is a large number of event wires in the '''FRP.NetWire.Event''' module. I will give you examples for some of the common ones here. It is worthwhile to have a look at the aforementioned module.
Line 242: Line 243:
   
 
<haskell>
 
<haskell>
after :: DTime -> Wire a (Event a)
+
after :: Time -> Wire m a a
 
</haskell>
 
</haskell>
   
The ''after'' wire causes an event after a certain number of seconds. This means that the output signal is ''Nothing'', until the specified time has passed, at which point the output becomes ''Just x'' for a single instant, where ''x'' is the input value at that instant. After that the event never happens again.
+
The ''after'' wire causes an event after a certain number of seconds. This means that the wire inhibits until the specified time has passed, at which point it runs for a single instant. After that the event never happens again, i.e. it always inhibits.
   
 
==== once ====
 
==== once ====
   
 
<haskell>
 
<haskell>
once :: Wire (Event a) (Event a)
+
once :: Wire m a a
 
</haskell>
 
</haskell>
   
  +
This wire produces an event at the first instant and never again.
This wire takes a potential event. It waits, until the event happens (i.e. the input becomes a ''Just''). It outputs the event once and then never again, even if the event happens again in the future.
 
   
 
==== repeatedly ====
 
==== repeatedly ====
   
 
<haskell>
 
<haskell>
repeatedly :: Wire (DTime, a) (Event a)
+
repeatedly :: Wire m (Time, a) a
 
</haskell>
 
</haskell>
   
Line 266: Line 267:
   
 
<haskell>
 
<haskell>
hold :: a -> Wire (Event a) a
+
hold :: Wire m a b -> Wire m a b
 
</haskell>
 
</haskell>
   
This wire turns events into continuous signals. At the beginning the output is the value given by the argument. Each time the input event occurs, the ouput switches to its value and keeps it until the next event occurs.
+
This wire turns events into continuous signals. It inhibits until the first signal from the argument wire. Each time the input event occurs, the output switches to its value and keeps it until the next event occurs.
   
 
=== Random numbers ===
 
=== Random numbers ===
Line 276: Line 277:
   
 
<haskell>
 
<haskell>
noise :: Wire a Double
+
noise :: Wire m a Double
 
</haskell>
 
</haskell>
   
Line 286: Line 287:
   
 
<haskell>
 
<haskell>
diff :: Eq a => Wire a (Event (a, Time))
+
diff :: Eq a => Wire m a (a, Time)
 
</haskell>
 
</haskell>
   
This wire emits an event, whenever the input signal changes. The event contains the last value as well as the time elapsed since then. One possible use case is file monitoring. Pass the file's modification time or even its contents as the input signal.
+
This wire emits an event, whenever the input signal changes. The event contains the last value as well as the time elapsed since then. One possible use case is file monitoring. Pass the file's modification time or even its contents as the input signal. This wire inhibits on no change.
   
 
Another useful wire is ''avg'', which computes the average value of the input signal over the specified number of most recent samples:
 
Another useful wire is ''avg'', which computes the average value of the input signal over the specified number of most recent samples:
   
 
<haskell>
 
<haskell>
avg :: Int -> Wire Double Double
+
avg :: Int -> Wire m Double Double
 
</haskell>
 
</haskell>
   
Line 300: Line 301:
   
 
<haskell>
 
<haskell>
avgOfNoise :: Wire a Double
+
avgOfNoise :: Wire m a Double
 
avgOfNoise = avg 1000 <<< noise
 
avgOfNoise = avg 1000 <<< noise
 
</haskell>
 
</haskell>
Line 307: Line 308:
   
 
<haskell>
 
<haskell>
avgFps :: Int -> Wire a Double
+
avgFps :: Int -> Wire m a Double
 
</haskell>
 
</haskell>
   
Line 321: Line 322:
   
 
<haskell>
 
<haskell>
highPeak :: (NFData a, Ord a) => Wire a a
+
highPeak :: (NFData a, Ord a) => Wire m a a
lowPeak :: (NFData a, Ord a) => Wire a a
+
lowPeak :: (NFData a, Ord a) => Wire m a a
 
</haskell>
 
</haskell>
   
Line 332: Line 333:
   
 
<haskell>
 
<haskell>
identifier :: Wire a Int
+
identifier :: MonadIO m => Wire m a Int
 
</haskell>
 
</haskell>
   
Line 339: Line 340:
 
=== Impure wires ===
 
=== Impure wires ===
   
As noted earlier wires are allowed to perform impure operations. There are three related utilities for this task:
+
As noted earlier wires are allowed to perform impure operations:
   
 
<haskell>
 
<haskell>
execute :: Wire (IO a) a
+
execute :: MonadIO m => Wire m (m a) a
 
</haskell>
 
</haskell>
   
The ''execute'' wire is the simplest wire for impure operations. It takes an ''IO'' action as its input signal and outputs its result. If the action throws an exception, then this wire inhibits. Signal inhibition is explained in a later section.
+
The ''execute'' wire is the simplest wire for impure operations. It takes an ''IO'' action as its input signal and outputs its result. If the action throws an exception, then this wire inhibits.
   
  +
You may want to combine this wire with the ''diff'' wire to develop a wire, which reacts to changes, or with the ''sample'' wire, which periodically samples a wire given a time delta, or with the ''swallow'' wire, which transmits the first signal from an input wire forever.
<haskell>
 
executeEvery :: Wire (DTime, IO a) a
 
</haskell>
 
 
The ''executeEvery'' wire is useful for monitoring external resources. It takes two input signals. The right signal is an ''IO'' action, which is executed at intervals given by the left signal. The output is the most recent result of the action. This wire inhibits, until the action has returned a result for the first time. Note that ''executeEvery'' adheres to the interval, even if the action throws an exception.
 
 
You may want to combine this wire with the ''diff'' wire to develop a wire, which reacts to changes.
 
   
 
<haskell>
 
<haskell>
executeOnce :: Wire (IO a) a
+
liftWire :: Monad m => Wire m (m a) a
 
</haskell>
 
</haskell>
   
  +
The ''liftWire'' wire lifts the given monadic computation to a wire. The action is run at every instant. This wire never inhibits.
The ''executeOnce'' wire executes the action given by the input signal once at each instant, until it succeeds without an exception. The wire inhibits, until a result is available, at which point it returns that result forever without executing the action ever again.
 
   
   
Line 367: Line 362:
   
 
<haskell>
 
<haskell>
myWire :: Wire Double Double
+
myWire :: Monad m => Wire m Double Double
 
myWire =
 
myWire =
 
proc x -> do
 
proc x -> do
Line 379: Line 374:
   
 
Another method to perform choice is to use one of the parallel switches, which are explained in a later section.
 
Another method to perform choice is to use one of the parallel switches, which are explained in a later section.
 
 
== Signal inhibition ==
 
 
A wire may choose not to return anything, at which point it is said to be inhibiting. If the whole wire network inhibits, then the stepping functions will return ''Nothing''. If a wire in a sequence of wires inhibits, the later wires are not run.
 
   
 
=== Inhibiting ===
 
=== Inhibiting ===
   
There are many ways to inhibit, the simplest being unconditional inhibition, which can be done with the ''inhibit'' wire:
+
There are many ways to inhibit, the simplest being unconditional inhibition, which can be done with the ''inhibit_'' wire:
   
 
<haskell>
 
<haskell>
inhibit :: Wire a b
+
inhibit_ :: Wire m a b
 
</haskell>
 
</haskell>
   
 
This wire disregards its input and doesn't return. Note that ''inhibit'' is just a better name for the ''zeroArrow'' wire from the ''ArrowZero'' type class. You can use that one, if you prefer.
 
This wire disregards its input and doesn't return. Note that ''inhibit'' is just a better name for the ''zeroArrow'' wire from the ''ArrowZero'' type class. You can use that one, if you prefer.
   
In general you would prefer inhibition based on a predicate, for which there exist multiple ways. One simple way is to use ''inhibit'' together with choice:
+
In general you would prefer inhibition based on a predicate, for which there exist multiple ways. One simple way is to use ''inhibit_'' together with choice:
   
 
<haskell>
 
<haskell>
waitOneSecond :: Wire a a
+
waitOneSecond :: Monad m => Wire m a a
 
waitOneSecond =
 
waitOneSecond =
 
proc x -> do
 
proc x -> do
 
t <- time -< ()
 
t <- time -< ()
if t < 1 then inhibit -< ()
+
if t < 1 then inhibit_ -< ()
 
else identity -< x
 
else identity -< x
 
</haskell>
 
</haskell>
Line 409: Line 399:
   
 
<haskell>
 
<haskell>
waitOneSecond :: Wire a a
+
waitOneSecond :: Monad m => Wire m a a
 
waitOneSecond =
 
waitOneSecond =
 
proc x -> do
 
proc x -> do
Line 420: Line 410:
   
 
<haskell>
 
<haskell>
swallow :: Wire a b -> Wire a b
+
swallow :: Wire m a b -> Wire m a b
 
</haskell>
 
</haskell>
   
Line 445: Line 435:
   
 
<haskell>
 
<haskell>
exhibit :: Wire a b -> Wire a (Maybe b)
+
exhibit :: Wire m a b -> Wire m a (Output b)
  +
-- Recall that Output ~ Left SomeExpection
 
</haskell>
 
</haskell>
   
It takes its argument wire and runs the input signal through it. If the inner wire inhibits, then ''exhibit'' returns ''Nothing''. It never inhibits. Thus the following identity holds:
+
It takes its argument wire and runs the input signal through it. If the inner wire inhibits, then ''exhibit'' returns a ''Left'' value. It never inhibits. Thus the following identity holds:
   
 
<haskell>
 
<haskell>

Revision as of 15:11, 6 October 2011

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 an underlying monad and its input and output types:

data Wire m 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 mentioned earlier in general a wire is a function, which can mutate itself over time. The session value captures the current state of the wire.

withWire :: (MonadIO m, MonadIO sm) => Wire m a b -> (Session m a b -> sm c) -> sm c
stepWire :: MonadIO m => a -> Session m a b -> m (Output 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 stepWireDelta function takes a time delta, and the stepWireTime function takes the current time (which doesn't need to be the real time):

stepWireDelta :: MonadIO m => NominalDiffTime -> a -> Session m a b -> m (Output b)
stepWireTime :: MonadIO m => UTCTime -> a -> Session m a b -> m (Output b)

Note that it is allowed to give zero or negative deltas and times, which are earlier than the last time. This lets you run the system backwards in time. If you do that, your wire should be prepared to handle it properly.

The stepping functions return a Output b, which is just an alias for Either SomeException b:

type Output = Either SomeException

If the wire inhibits (which is analogous to raising an exception), then the result is Left SomeException, otherwise it will be Right b, with b being the output. Here is a complete example:

{-# LANGUAGE Arrows #-}

module Main where

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


myWire :: Wire IO () 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 IO () String -> IO ()
    loop session =
        forever $ do
            output <- stepWire () session
            case output of
              Left e -> print e
              Right x  -> putStrLn x

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 session from multiple threads. This makes it easy to implement conditional stepping based on system events.

Note: The type signatures of all Wires have an implicit Monad constraint on its first parameter. This constraint has been omit for the sake of brevity.

Signal inhibition

A wire may choose not to return anything, at which point it is said to be inhibiting. If the whole wire network inhibits, then the stepping functions will return Left e, where e :: SomeException. Otherwise, a Right value is returned. If a wire in a sequence of wires inhibits, the later wires are not run.

Writing a wire

I will assume that you are familiar with arrow notation, and I will use it instead of the raw arrow combinators most of the time. If you haven't used arrow notation before, see the GHC arrow notation manual.

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.

Time is measured in Double in Netwire. To improve type signatures there is a type aliases defined for you:

type Time = Double

Time is used to refer to local time and time deltas, i.e. time differences. It is represented in seconds.

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 m 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 m 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 m a Time

As the type suggests, time is measured in seconds and represented as a Time. 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 :: Time -> Wire a Time

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.

Calculus

One of the compelling features of FRP is integration and differentiation over time. It is a very cheap operation to integrate over time. In fact the time wire you have seen in the last section is really just the integral of the constant 1. Here is the type of the integral wire, which integrates over time:

integral :: Double -> Wire m Double Double

The argument is the integration constant or starting value. The input is the subject of integration. Let's write a clock, which runs at half the speed of the real clock:

slowClock :: Wire m a Double
slowClock = proc _ -> integral 0 -< 0.5

Since the integration constant is 0, the time will start at zero. Integration becomes more interesting, as soon as you integrate non-constants:

particle :: Monad m => Wire m a Double
particle =
    proc _ -> do
        v <- integral 1 -< -0.1
        integral 15 -< v

This wire models a one-dimensional particle, which starts at position 15 and velocity +1. A constant acceleration of -0.1 per second per second is applied to the velocity, hence the particle moves right towards positive infinity at first, while gradually becoming slower, until it reverses its direction and moves left towards negative infinity.

The above type signature is actually a special case, which I provided for the sake of simplicity. The real type signature is a bit more interesting:

integral ::
    (Monad m, NFData v, VectorSpace v, Scalar v ~ Double) =>
    v -> Wire m v v

You can integrate over time in any real vector space. Some examples of vector spaces include tuples, complex numbers and any type, for which you define NFData and VectorSpace instances. Let's see the particle example in two dimensions:

particle2D :: Monad m => Wire m a (Double, Double)
particle2D =
    proc _ -> do
        v <- integral (1, -0.5) -< (-0.1, 0.4)
        integral (0, 0) -< v

Differentiation works similarly, although there are two variants:

derivative     :: Wire m Double Double
derivativeFrom :: Double -> Wire m Double Double

The difference between the two variants is that derivative will inhibit at the first instant (inhibition is explained later), because it needs at least two samples to compute the rate of change over time. The derivativeFrom variant does not have that shortcoming, but you need to provide the first sample as an argument.

Again I have simplified the types to help understanding. Just like with integration you can differentiate over any vectorspace, as long as your type has an NFData instance.

Events

Events are a useful tool to add discrete values to the system. As the name states an event usually denotes some condition or external event, which can be present at some instants and absent at others. A common use case for events is user input. Events are wires that run if the event that it models has occurred and inhibit if otherwise.

There is a large number of event wires in the FRP.NetWire.Event module. I will give you examples for some of the common ones here. It is worthwhile to have a look at the aforementioned module.

after

after :: Time -> Wire m a a

The after wire causes an event after a certain number of seconds. This means that the wire inhibits until the specified time has passed, at which point it runs for a single instant. After that the event never happens again, i.e. it always inhibits.

once

once :: Wire m a a

This wire produces an event at the first instant and never again.

repeatedly

repeatedly :: Wire m (Time, a) a

This wire takes two input signals. It produces events repeatedly after the time delta given by the left signal. This delta can change over time, making the event happen more or less frequently. The right signal is the desired event value.

hold

hold :: Wire m a b -> Wire m a b

This wire turns events into continuous signals. It inhibits until the first signal from the argument wire. Each time the input event occurs, the output switches to its value and keeps it until the next event occurs.

Random numbers

Netwire provides a few wires for random noise generation. Probably the most important one is the noise wire:

noise :: Wire m a Double

This wire outputs a random number between 0 (inclusive) and 1 (exclusive). The underlying random number generator is a fast implementation of the Mersenne Twister algorithm provided by Don Stewart's mersenne-random package.

Signal analysis

Netwire provides some wires to perform signal analysis. One useful wire is diff:

diff :: Eq a => Wire m a (a, Time)

This wire emits an event, whenever the input signal changes. The event contains the last value as well as the time elapsed since then. One possible use case is file monitoring. Pass the file's modification time or even its contents as the input signal. This wire inhibits on no change.

Another useful wire is avg, which computes the average value of the input signal over the specified number of most recent samples:

avg :: Int -> Wire m Double Double

Since the noise wire returns random numbers between 0 and 1, if you pass the output of noise through avg x you should get a value close to 0.5, if the argument x is suitably large:

avgOfNoise :: Wire m a Double
avgOfNoise = avg 1000 <<< noise

An interesting special case of avg is the avgFps wire, which is very useful for performance analysis. It returns the average frames per second:

avgFps :: Int -> Wire m a Double

Both avg and avgFps calculate the average over a certain number of most recent samples. While they have a constant time complexity O(1) they have a linear space complexity of O(n), where n is the number of samples. In some cases it can be fine to consider calculating the average over all samples forever. The avgAll wire does exactly that:

avgAll :: Wire Double Double

Unlike avg and avgFps this variant uses not only constant time, but also constant space.

There are also wires for finding peaks. The highPeak and lowPeak wires output the high and low peaks respectively for their input:

highPeak :: (NFData a, Ord a) => Wire m a a
lowPeak  :: (NFData a, Ord a) => Wire m a a

Again the type signatures are only special cases. See the library documentation for the real types. In short, you can get averages of any fractional input value.

Unique request numbers

Sometimes you might want to generate numbers, which are unique throughout the wire session. For example you might want to manage game objects, open file handles or something similar. The identifier wire generates such unique numbers:

identifier :: MonadIO m => Wire m a Int

At the first instance it chooses a unique number and then returns that number forever.

Impure wires

As noted earlier wires are allowed to perform impure operations:

execute :: MonadIO m => Wire m (m a) a

The execute wire is the simplest wire for impure operations. It takes an IO action as its input signal and outputs its result. If the action throws an exception, then this wire inhibits.

You may want to combine this wire with the diff wire to develop a wire, which reacts to changes, or with the sample wire, which periodically samples a wire given a time delta, or with the swallow wire, which transmits the first signal from an input wire forever.

liftWire :: Monad m => Wire m (m a) a

The liftWire wire lifts the given monadic computation to a wire. The action is run at every instant. This wire never inhibits.


Choice

Wires can branch into multiple subwires, sending a signal to a subset of them. The easiest method to do that is using the ArrowChoice instance, which effectively enables you to use if and case inside of arrow notation:

myWire :: Monad m => Wire m Double Double
myWire =
    proc x -> do
        t <- time -< ()
        if t < 4
          then identity -< x
          else integral 0 -< 0.2

This wire acts like the identity wire for four seconds and then switches into a clock, which starts at 0 and runs at 1/5 of the speed of time. The clock indeed starts at 0, because choice is exclusive. The wires, which have not been chosen are suspended. This effectively freezes their local time.

Another method to perform choice is to use one of the parallel switches, which are explained in a later section.

Inhibiting

There are many ways to inhibit, the simplest being unconditional inhibition, which can be done with the inhibit_ wire:

inhibit_ :: Wire m a b

This wire disregards its input and doesn't return. Note that inhibit is just a better name for the zeroArrow wire from the ArrowZero type class. You can use that one, if you prefer.

In general you would prefer inhibition based on a predicate, for which there exist multiple ways. One simple way is to use inhibit_ together with choice:

waitOneSecond :: Monad m => Wire m a a
waitOneSecond =
    proc x -> do
        t <- time -< ()
        if t < 1 then inhibit_ -< ()
                 else identity -< x

This wire inhibits for one second and after that acts like the identity wire. Note that there is another way to write this wire using some of the predefined wires:

waitOneSecond :: Monad m => Wire m a a
waitOneSecond =
    proc x -> do
        ev <- after 1 -< ()
        swallow wait -< ev
        identity -< x

The after wire was explained earlier. It will emit an event after one second. The wait wire extracts the event's value and returns it, unless no event happened, at which point it simply inhibits. However, the event occurs only once, so this would normally act like the identity wire for an instant and then return to inhibition. This is where swallow comes into play.

swallow :: Wire m a b -> Wire m a b

The swallow wire encapsulates the wire given as its argument and modifies its behaviour in the following way: As long as the inner wire inhibits, the swallow wire also inhibits, but as soon as the inner wire produces a result, swallow switches into the constant wire with that result. In other words, it waits for the first signal from the inner wire and then keeps that result forever.

In this case wait would only produce a result once, but because it is wrapped by swallow this result is kept forever and the inner wait wire is dropped from the network.

The swallow function is actually our first wire transformer. It takes a wire and encapsulates it modifying its behaviour.

Combining

You can combine two wires using the <+> combinator. This combinator comes from the ArrowPlus class and takes two wires as its argument. It passes the signal through the left wire. If that wire inhibits, it passes the signal to the right wire. The result of the first non-inhibiting wire is returned. If both wires inhibit, their combination inhibits.

Note that if the first wire results, the second one is not run at all, thus <+> is left-biased. The following identities hold:

w1 <+> inhibit = w1
inhibit <+> w2 = w2

Exhibition

Sometimes you may want to observe inhibition. You can use the exhibit wire transformer for that purpose:

exhibit :: Wire m a b -> Wire m a (Output b)
-- Recall that Output ~ Left SomeExpection

It takes its argument wire and runs the input signal through it. If the inner wire inhibits, then exhibit returns a Left value. It never inhibits. Thus the following identity holds:

exhibit w1 <+> w2 = exhibit w1

Note that this suggests correctly that signal inhibition can be interpreted as arrow exceptions, and exhibit acts like the try combinator.