Difference between revisions of "Netwire"

From HaskellWiki
Jump to navigation Jump to search
m (→‎Pure stateful wires: TODO notice.)
(43 intermediate revisions by 4 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.
+
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.
  +
  +
* [http://hackage.haskell.org/package/netwire Download netwire]
  +
  +
This wiki page corresponds to Netwire version 3 and is currently a work in progress.
   
   
 
== Features ==
 
== Features ==
   
Here is a list of some of the features of ''netwire'':
+
Here is a list of some of the features of Netwire:
   
* arrowized interface,
+
* arrow interface (or optionally an applicative interface),
  +
* signal inhibition (ArrowZero / Alternative),
* applicative interface,
 
* signal inhibition (''ArrowZero'' / ''Alternative''),
+
* signal selection (ArrowPlus / Alternative),
  +
* self-adjusting wires (ArrowChoice),
* choice and combination (''ArrowPlus'' / ''Alternative''),
 
* self-adjusting wires (''ArrowChoice''),
 
 
* rich set of event wires,
 
* rich set of event wires,
 
* signal analysis wires (average, peak, etc.),
 
* signal analysis wires (average, peak, etc.),
* impure wires.
+
* effectful wires.
   
== Quickstart ==
 
   
  +
== Basics ==
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 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:
=== The wire ===
 
   
  +
<haskell>
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.
 
  +
import Control.Wire
   
  +
data Wire e (>~) a b
A wire is parameterized over its input and output types:
 
  +
</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>
 
<haskell>
data Wire a b
+
comp :: Wire e (>~) a b
 
</haskell>
 
</haskell>
   
  +
Values of type <hask>Wire e (>~) a b</hask> are time-varying functions, which resemble the following type:
   
  +
<haskell>
=== Differences from Yampa ===
 
  +
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.
If you are not familiar with Yampa or Animas, you can safely skip this section.
 
   
  +
=== The inhibition monoid ===
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.
 
   
  +
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>.
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:
 
  +
  +
=== 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>
 
<haskell>
  +
type MyWire = Wire () (Kleisli IO)
w = w1 <+> w2
 
 
</haskell>
 
</haskell>
   
The ''w'' wire runs its signal through the wire ''w1'', and if it inhibits, it passes the signal to ''w2''.
 
   
  +
== Running wires ==
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.
 
   
  +
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:
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.
 
   
  +
<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:
=== 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.
 
   
 
<haskell>
 
<haskell>
initWire :: Wire a b -> (Session a b -> IO c) -> IO c
+
stepWireM :: MyWire a b -> a -> IO (Either () b, MyWire a b)
stepWire :: a -> Session a b -> IO (Maybe b)
 
 
</haskell>
 
</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:
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:
 
   
 
<haskell>
 
<haskell>
  +
system :: MyWire Int String
{-# LANGUAGE Arrows #-}
 
  +
system = {- ... -}
   
  +
main :: IO ()
module Main where
 
  +
main = loop system
  +
where
  +
loop :: MyWire Int String -> IO ()
  +
loop w' = do
  +
(mx, w) <- stepWireM w' 15
   
  +
{- ... do something with mx ... -}
import Control.Monad
 
import FRP.NetWire
 
import Text.Printf
 
   
  +
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.
myWire :: Wire () String
 
myWire =
 
proc _ -> do
 
t <- time -< ()
 
fps <- avgFps 1000 -< ()
 
fpsPeak <- highPeak -< fps
 
   
  +
=== Testing wires ===
if t < 4
 
then identity -< "Waiting four seconds."
 
else identity -<
 
printf "Got them! (%8.0f FPS, peak: %8.0f)"
 
fps fpsPeak
 
   
  +
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 :: IO ()
main = withWire myWire loop
+
main = testWireM 1000 (return 15) system
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'
 
 
</haskell>
 
</haskell>
   
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.
 
   
  +
== Writing wires ==
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.
 
   
  +
=== 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):
=== Writing a wire ===
 
   
  +
<haskell>
==== Time ====
 
  +
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:
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.
 
   
  +
<haskell>
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.
 
  +
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.
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.
 
   
  +
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:
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.
 
   
  +
<haskell>
==== Pure stateless wires ====
 
  +
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.
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:
 
  +
  +
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:
   
 
<haskell>
 
<haskell>
  +
stepWireM (countFrom 15) inp
identity :: Wire a a
 
  +
-> (Right 15, countFrom 16)
  +
  +
stepWireM (countFrom 16) inp
  +
-> (Right 16, countFrom 17)
 
</haskell>
 
</haskell>
   
  +
=== Composing wires ===
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:
 
  +
  +
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>
 
<haskell>
constant :: b -> Wire a b
+
system :: MyWire a String
  +
system =
  +
proc _ -> do
  +
c1 <- countFrom 10 -< ()
  +
c2 <- countFrom 20 -< ()
  +
identity -< printf "%d %d" (c1 :: Int) (c2 :: Int)
 
</haskell>
 
</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:
If you run the wire <code>constant 15</code>, you will get as output the number 15 all the time, regardless of the current time and the input.
 
   
  +
<haskell>
:'''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''.
 
  +
stepWireM system ()
   
  +
1st instant: Right "10 20"
==== Pure stateful wires ====
 
  +
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:
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.
 
   
 
<haskell>
 
<haskell>
time :: Wire a Double
+
main :: IO ()
  +
main = testWireM 1000 (return ()) system
 
</haskell>
 
</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''. As a side note the ''identity'' wire behaves like ''returnA''.
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:
 
  +
  +
The main feature to note here is that all of the subwires in the composition evolve individually. So in the second instant, each of the two counters will have gone up by one. This alone gives you a powerful abstraction for stateful computations. The equivalent when using a state monad or mutable variables would be to have a global state value with two counter values. By having time-varying functions you can have something called ''local state''. Each of the two counters (or as many as you use) have their own individual local state, which is the current counter value. This is way more convenient and composable than a state monad or other imperative state abstractions.
  +
  +
=== Choice ===
  +
  +
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> constructs:
   
 
<haskell>
 
<haskell>
  +
system =
timeFrom :: Double -> Wire a Double
 
  +
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>
 
</haskell>
   
  +
If the <hask>c1</hask> signal is even, then the wire outputs the string "We don't want even c1". Otherwise it takes the second path. Here it is important to know that the second counter will be suspended, when <hask>c1</hask> is even, because the <hask>else</hask> branch is not reached. A wire can only evolve, when it is actually reached. So in this example <hask>c2</hask> will run at half the speed of <hask>c1</hask> and the output will look like:
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.
 
  +
  +
<haskell>
  +
1st instant: "We don't want even c1"
  +
2nd instant: "11 20"
  +
3rd instant: "We don't want even c1"
  +
4th instant: "13 21"
  +
5th instant: "We don't want even c1"
  +
6th instant: "15 22"
  +
7th instant: "We don't want even c1"
  +
</haskell>
   
  +
[[Category:FRP]]
'''TODO''': More to come.
 

Revision as of 18:17, 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


Writing wires

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)

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 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:

stepWireM (countFrom 15) inp
-> (Right 15, countFrom 16)

stepWireM (countFrom 16) inp
-> (Right 16, countFrom 17)

Composing wires

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:

system :: MyWire a String
system =
    proc _ -> do
        c1 <- countFrom 10 -< ()
        c2 <- countFrom 20 -< ()
        identity -< printf "%d %d" (c1 :: Int) (c2 :: Int)

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:

stepWireM system ()

1st instant: Right "10 20"
2nd instant: Right "11 21"
3rd instant: Right "12 22"

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:

main :: IO ()
main = testWireM 1000 (return ()) system

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 () to the two counters (which ignore their input signals, too). It takes the output signals c1 and c2 and makes a formatted string out of them. Finally this string is passed to the identity wire. This is the last wire in the signal network system, so its output signal is the output signal of system. As a side note the identity wire behaves like returnA.

The main feature to note here is that all of the subwires in the composition evolve individually. So in the second instant, each of the two counters will have gone up by one. This alone gives you a powerful abstraction for stateful computations. The equivalent when using a state monad or mutable variables would be to have a global state value with two counter values. By having time-varying functions you can have something called local state. Each of the two counters (or as many as you use) have their own individual local state, which is the current counter value. This is way more convenient and composable than a state monad or other imperative state abstractions.

Choice

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 case and if constructs:

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)

If the c1 signal is even, then the wire outputs the string "We don't want even c1". Otherwise it takes the second path. Here it is important to know that the second counter will be suspended, when c1 is even, because the else branch is not reached. A wire can only evolve, when it is actually reached. So in this example c2 will run at half the speed of c1 and the output will look like:

1st instant: "We don't want even c1"
2nd instant: "11 20"
3rd instant: "We don't want even c1"
4th instant: "13 21"
5th instant: "We don't want even c1"
6th instant: "15 22"
7th instant: "We don't want even c1"