|
|
(8 intermediate revisions by 2 users not shown) |
Line 1: |
Line 1: |
| Netwire is a library for [[Functional Reactive Programming|functional reactive programming]], which uses the concept of [[Arrow|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. | | Netwire is a [[Functional Reactive Programming|functional reactive programming]] library that provides both an applicative and an arrow interface. It allows you to express time-varying values with a rich event system. |
| | |
| * [http://hackage.haskell.org/package/netwire Download netwire]
| |
| | |
| This wiki page corresponds to Netwire version 3 and is currently a work in progress.
| |
|
| |
|
| | * [http://hackage.haskell.org/package/netwire Project page] |
| | * [http://hub.darcs.net/ertes/netwire Source repository] |
|
| |
|
| == Features == | | == Features == |
Line 10: |
Line 8: |
| Here is a list of some of the features of Netwire: | | Here is a list of some of the features of Netwire: |
|
| |
|
| * arrow interface (or optionally an applicative interface), | | * applicative interface (or optionally an arrow interface), |
| * signal inhibition (ArrowZero / Alternative), | | * signal intervals, |
| * signal selection (ArrowPlus / Alternative), | | * dynamic switching, |
| * self-adjusting wires (ArrowChoice),
| | * rich set of predefined functionality, |
| * rich set of event wires, | | * signal analysis (average, interpolation, peak, etc.), |
| * signal analysis wires (average, peak, etc.), | | * effectful reactive systems. |
| * effectful wires. | |
| | |
| | |
| == Basics ==
| |
| | |
| The Netwire library is based around a data type called <hask>Wire</hask>. You need to import the <hask>Control.Wire</hask> module to work with wires:
| |
| | |
| <haskell>
| |
| import Control.Wire
| |
| | |
| data Wire e (>~) a b
| |
| </haskell>
| |
| | |
| For some arrows <hask>(>~)</hask> and all monoids <hask>e</hask> the type <hask>Wire e (>~)</hask> is an arrow. Only certain arrows are allowed for <hask>(>~)</hask>, because <hask>Wire</hask> is actually a data family. These arrows are called base arrows in Netwire.
| |
| | |
| <haskell>
| |
| comp :: Wire e (>~) a b
| |
| </haskell>
| |
| | |
| Values of type <hask>Wire e (>~) a b</hask> are time-varying functions, which resemble the following type:
| |
| | |
| <haskell>
| |
| a >~ Either e b
| |
| </haskell>
| |
| | |
| So it's a function that takes a value of type <hask>a</hask> and either produces a value of type <hask>b</hask> or produces no value, but instead ''inhibits'' with a value of type <hask>e</hask>. 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 <hask>e</hask> argument to <hask>Wire</hask> is called the inhibition monoid. For simple applications you can just use <hask>()</hask> here, but you may want to actually assign exception values to inhibition. We will cover that later. For now just use <hask>()</hask>.
| |
| | |
| === Base arrows ===
| |
| | |
| The <hask>(>~)</hask> argument to <hask>Wire</hask> is called the base arrow. In most cases you will use a <hask>Kleisli</hask> 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 <hask>IO</hask> monad, and it is useful to define a type alias for your custom wire type:
| |
| | |
| <haskell>
| |
| type MyWire = Wire () (Kleisli IO)
| |
| </haskell>
| |
| | |
| | |
| == Running wires ==
| |
| | |
| For running a wire you can use the stepping functions available in the <hask>Control.Wire.Session</hask> module. There is no need to import that module. It is automatically imported with <hask>Control.Wire</hask>. For Kleisli-based wires you will want to use the <hask>stepWireM</hask> function:
| |
| | |
| <haskell>
| |
| stepWireM ::
| |
| Monad m
| |
| => Wire e (Kleisli m) a b
| |
| -> a
| |
| -> m (Either e b, Wire e (Kleisli m) a b)
| |
| </haskell>
| |
| | |
| In our case we have <hask>m = IO</hask>, so our type signature is simply:
| |
| | |
| <haskell>
| |
| stepWireM :: MyWire a b -> a -> IO (Either () b, MyWire a b)
| |
| </haskell>
| |
| | |
| This function takes a wire and an input value. It passes the input value to the wire and returns its result value of type <hask>Either () b</hask>. Along with the result it also returns a new wire. Normally you would call <hask>stepWireM</hask> in a loop, which performs instant after instant. This is the basic structure:
| |
| | |
| <haskell>
| |
| 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.
| |
| </haskell>
| |
| | |
| 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 <hask>testWireM</hask>:
| |
| | |
| <haskell>
| |
| testWireM ::
| |
| (Show e, MonadIO m)
| |
| => Int
| |
| -> m a
| |
| -> Wire e (Kleisli m) a String
| |
| -> m ()
| |
| </haskell>
| |
| | |
| 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. <hask>testWireM</hask> prints the output continuously on a single line:
| |
| | |
| <haskell>
| |
| main :: IO ()
| |
| 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>
| | == Scope == |
| 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:
| | Netwire's FRP framework is intended to be used for continuous applications. It replaces the traditional big main loop with its global state and event callbacks/branching by a completely declarative model. The following types of applications can benefit from using Netwire: |
|
| |
|
| <haskell>
| | * artificial intelligence and bots, |
| stepWireM (constant 15) inp
| | * canvas-based graphics and animations, |
| -> (Right 15, constant 15) | | * continuous signal synthesis (audio waves, etc.), |
| </haskell>
| | * games and game servers, |
| | * scene-based user interfaces (like OpenGL and vty), |
| | * simulations. |
|
| |
|
| 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.
| | If you can sensibly break your application down into ''frames'', then Netwire is for you. For other kinds of reactive applications like widget-based UIs you may want to look into [[reactive-banana]] instead. |
|
| |
|
| 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>
| | == Get started == |
| stepWireM identity inp
| |
| -> (Right inp, identity)
| |
| </haskell>
| |
|
| |
|
| Both identity and constant wires are examples of ''stateless'' wires. They don't change over time. You can see this in the stepping examples above. They always return themselves for the next instant.
| | The documentation is contained within the package itself, but you can also read it online: |
|
| |
|
| The ''countFrom'' function takes a starting value and returns a wire that returns sequential values instant by instant. This is the first example of a ''stateful'' wire, because it changes over time:
| | * [http://hub.darcs.net/ertes/netwire/browse/README.md Tutorial] |
| | * [http://hackage.haskell.org/package/netwire Project page with API docs] |
|
| |
|
| <haskell>
| |
| stepWireM (countFrom 15) inp
| |
| -> (Right 15, countFrom 16)
| |
|
| |
|
| stepWireM (countFrom 16) inp
| | === Other reading === |
| -> (Right 16, countFrom 17)
| |
| </haskell>
| |
|
| |
|
| === Composing wires ===
| | * [http://todayincode.tumblr.com/post/96914679355/almost-a-netwire-5-tutorial Almost a Netwire 5 Tutorial] |
|
| |
|
| The main feature of wires is that you can compose them using the arrow interface. There is a rich set of ways for composing, and you will want to use arrow notation for your convenience:
| |
|
| |
|
| <haskell>
| | === Examples === |
| system :: MyWire a String
| |
| system =
| |
| proc _ -> do
| |
| c1 <- countFrom 10 -< ()
| |
| c2 <- countFrom 20 -< ()
| |
| identity -< printf "%d %d" (c1 :: Int) (c2 :: Int)
| |
| </haskell>
| |
|
| |
|
| In applications it is common to write wires that ignore their input. For those wires you should make the input type fully polymorphic to indicate this. Running this wire produces:
| | * [https://github.com/ScrambledEggsOnToast/tetris-hs tetris-hs] |
|
| |
|
| <haskell>
| |
| stepWireM system ()
| |
|
| |
|
| 1st instant: Right "10 20"
| | == Model and correctness == |
| 2nd instant: Right "11 21"
| |
| 3rd instant: Right "12 22"
| |
| </haskell>
| |
|
| |
|
| Note: You can use the ''testWireM'' function with this wire. The following action will run the wire continuously printing its result at every 1000th instant:
| | Netwire's underlying abstraction is more powerful than the [http://conal.net/papers/icfp97/ original formulation of time-varying values]. It allows you to implement general component systems with local state. |
|
| |
|
| <haskell> | | Starting with Netwire 5 there are two module trees <hask>Control.Wire</hask> and <hask>FRP.Netwire</hask>. The latter exports a subset of Netwire that closely follows the original model and provides a set of predefined FRP wires. |
| main :: IO ()
| |
| main = testWireM 1000 (return ()) system
| |
| </haskell> | |
|
| |
|
| In the FRP context we often talk about ''signals''. Particularly in the context of ''arrowized'' FRP (AFRP) like Netwire we talk about ''signal networks'' and signals passing through them. The ''system'' wire is your first signal network. It ignores its input signal and passes the signal <hask>()</hask> to the two counters (which ignore their input signals, too). It takes the output signals <hask>c1</hask> and <hask>c2</hask> and makes a formatted string out of them. Finally this string is passed to the <hask>identity</hask> wire. This is the last wire in the signal network ''system'', so its output signal is the output signal of ''system''. Side note: The ''identity'' wire behaves like ''returnA''.
| | Signal intervals are an extension of the original model and an integral part of Netwire: A behavior is a ''partial'' function of time with the limitation that both the defined and undefined intervals must have a non-zero length. This extension makes it much easier to express switching and multicasting systems. |
|
| |
|
| === Choice === | | == History == |
|
| |
|
| In traditional AFRP solutions like Yampa the path of a signal is fully determined by the structure of the signal network. In Netwire a signal can choose one of multiple paths by using the <hask>case</hask> and <hask>if</hask>:
| | This project started in 2011 as a replacement for Yampa to provide both a nicer interface and better integration into existing frameworks. Its original purpose was to power game servers and intelligent network bots. That's the origin of the name ''Netwire''. |
|
| |
|
| <haskell>
| | However, before its first release ''signal intervals'' were added (originally under the term ''signal inhibition''). Netwire became a completely new abstraction, so it lost its connection to Yampa. |
| system =
| |
| proc _ -> do
| |
| c1 <- countFrom 10 -< ()
| |
| if even c1
| |
| then returnA -< "We don't want even c1"
| |
| else do
| |
| c2 <- countFrom 20 -< ()
| |
| returnA -< printf "%d %d" (c1 :: Int) (c2 :: Int)
| |
| </haskell>
| |
|
| |
|
| [[Category:FRP]] | | [[Category:FRP]] |