Netwire: Difference between revisions
(Writing wires) |
|||
Line 4: | Line 4: | ||
This wiki page corresponds to Netwire version 3 and is currently a work in progress. | This wiki page corresponds to Netwire version 3 and is currently a work in progress. | ||
== Features == | == Features == | ||
Line 16: | Line 17: | ||
* signal analysis wires (average, peak, etc.), | * signal analysis wires (average, peak, etc.), | ||
* effectful wires. | * effectful wires. | ||
== Basics == | == Basics == | ||
Line 52: | Line 54: | ||
type MyWire = Wire () (Kleisli IO) | type MyWire = Wire () (Kleisli IO) | ||
</haskell> | </haskell> | ||
== Running wires == | == Running wires == | ||
Line 109: | Line 112: | ||
main :: IO () | main :: IO () | ||
main = testWireM 1000 (return 15) system | main = testWireM 1000 (return 15) system | ||
</haskell> | |||
== Predefined wires == | |||
There are numerous predefined wires, which you can compose using the arrow interface. We will practice that with three very simple predefined wires (the type signatures are simplified for the sake of learning): | |||
<haskell> | |||
constant :: b -> Wire e (>~) a b | |||
identity :: Wire e (>~) b b | |||
countFrom :: Enum b => b -> Wire e (>~) a b | |||
</haskell> | |||
The ''constant'' function takes an output value and produces a wire which produces that value constantly. So the wire <hask>constant 15</hask> will output 15 constantly at every instant. In other words, <hask>stepWireM</hask> will return <hask>Right 15</hask> along with a new wire that outputs 15 again: | |||
<haskell> | |||
stepWireM (constant 15) inp | |||
-> (Right 15, constant 15) | |||
</haskell> | |||
Note the fully polymorphic input type <hask>a</hask>. This basically means that the wire disregards its input, so whatever <hask>inp</hask> is, it is ignored. | |||
The ''identity'' wire is slightly more interesting. It has input and output of type <hask>b</hask>. What it does is: It simply outputs its input value at every instant: | |||
<haskell> | |||
stepWireM identity inp | |||
-> (Right inp, identity) | |||
</haskell> | </haskell> | ||
[[Category:FRP]] | [[Category:FRP]] |
Revision as of 16:48, 1 December 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 and has many additional features.
This wiki page corresponds to Netwire version 3 and is currently a work in progress.
Features
Here is a list of some of the features of Netwire:
- arrow interface (or optionally an applicative interface),
- signal inhibition (ArrowZero / Alternative),
- signal selection (ArrowPlus / Alternative),
- self-adjusting wires (ArrowChoice),
- rich set of event wires,
- signal analysis wires (average, peak, etc.),
- effectful wires.
Basics
The Netwire library is based around a data type called Wire
. You need to import the Control.Wire
module to work with wires:
import Control.Wire
data Wire e (>~) a b
For some arrows (>~)
and all monoids e
the type Wire e (>~)
is an arrow. Only certain arrows are allowed for (>~)
, because Wire
is actually a data family. These arrows are called base arrows in Netwire.
comp :: Wire e (>~) a b
Values of type Wire e (>~) a b
are time-varying functions, which resemble the following type:
a >~ Either e b
So it's a function that takes a value of type a
and either produces a value of type b
or produces no value, but instead inhibits with a value of type e
. The act of running a wire is called stepping and the process is called an instant. You can step a wire through one of the stepping functions, which we will cover later. When you step a wire, it will return a new version of itself along with its result. You are supposed to call the new version the next time you step.
The inhibition monoid
The e
argument to Wire
is called the inhibition monoid. For simple applications you can just use ()
here, but you may want to actually assign exception values to inhibition. We will cover that later. For now just use ()
.
Base arrows
The (>~)
argument to Wire
is called the base arrow. In most cases you will use a Kleisli
arrow here, and this is currently the only type of arrow supported, though more will be added in the future. For simple applications you can just use the IO
monad, and it is useful to define a type alias for your custom wire type:
type MyWire = Wire () (Kleisli IO)
Running wires
For running a wire you can use the stepping functions available in the Control.Wire.Session
module. There is no need to import that module. It is automatically imported with Control.Wire
. For Kleisli-based wires you will want to use the stepWireM
function:
stepWireM ::
Monad m
=> Wire e (Kleisli m) a b
-> a
-> m (Either e b, Wire e (Kleisli m) a b)
In our case we have m = IO
, so our type signature is simply:
stepWireM :: MyWire a b -> a -> IO (Either () b, MyWire a b)
This function takes a wire and an input value. It passes the input value to the wire and returns its result value of type Either () b
. Along with the result it also returns a new wire. Normally you would call stepWireM
in a loop, which performs instant after instant. This is the basic structure:
system :: MyWire Int String
system = {- ... -}
main :: IO ()
main = loop system
where
loop :: MyWire Int String -> IO ()
loop w' = do
(mx, w) <- stepWireM w' 15
{- ... do something with mx ... -}
loop w -- loop with the new wire.
Note: Even though the FRP idea suggests it, there is no reason to run wires continuously or even regularly. You can totally have an instant depending on user input, a GUI event or network traffic, so instants can be minutes apart.
Testing wires
There is a convenient function for testing wires, which does all the plumbing for you. It's called testWireM
:
testWireM ::
(Show e, MonadIO m)
=> Int
-> m a
-> Wire e (Kleisli m) a String
-> m ()
For wires returning a string, you can easily test them using this function. The first argument is a FPS/accuracy tradeoff. If it's 100, it will only print the output of every 100th instant. The second argument is an input generator action. At each instant, this action is run and its result is passed as input to the wire. The wire's output is then printed. testWireM
prints the output continuously on a single line:
main :: IO ()
main = testWireM 1000 (return 15) system
Predefined wires
There are numerous predefined wires, which you can compose using the arrow interface. We will practice that with three very simple predefined wires (the type signatures are simplified for the sake of learning):
constant :: b -> Wire e (>~) a b
identity :: Wire e (>~) b b
countFrom :: Enum b => b -> Wire e (>~) a b
The constant function takes an output value and produces a wire which produces that value constantly. So the wire constant 15
will output 15 constantly at every instant. In other words, stepWireM
will return Right 15
along with a new wire that outputs 15 again:
stepWireM (constant 15) inp
-> (Right 15, constant 15)
Note the fully polymorphic input type a
. This basically means that the wire disregards its input, so whatever inp
is, it is ignored.
The identity wire is slightly more interesting. It has input and output of type b
. What it does is: It simply outputs its input value at every instant:
stepWireM identity inp
-> (Right inp, identity)