Difference between revisions of "User:Echo Nolan/Reactive Banana: Straight to the Point"

From HaskellWiki
Jump to navigation Jump to search
 
(3 intermediate revisions by the same user not shown)
Line 162: Line 162:
 
</pre-haskell>
 
</pre-haskell>
   
Now how do we hook that up to FRP? We already know fmap, so we can get something of type <code-haskell>Event t Note -> Event t [Note]</code-haskell> but how do we get a list of <code-haskell>Note</code-haskell>s to play at the same time? Meet a new combinator:
+
Now how do we hook that up to FRP? We already know fmap, so we can get something of type <code-haskell>Event t Note -> Event t [Note]</code-haskell>, but how do we get a list of <code-haskell>Note</code-haskell>s to play at the same time? Meet a new combinator:
   
 
<pre-haskell>
 
<pre-haskell>
Line 189: Line 189:
 
return network
 
return network
 
</pre-haskell>
 
</pre-haskell>
  +
  +
== This banana is getting crowded! Plugging in a clock ==
  +
  +
Let's take our metronome and turn it into a beat counting metronome. Then we can play some scales and other patterns - like when we played around with <code-haskell>threadDelay</code-haskell>, <code-haskell>intersperse</code-haskell> and <code-haskell>sequence_</code-haskell> back in section 2. Meet <code-haskell>accumE</code-haskell>:
  +
  +
<pre-haskell>
  +
accumE :: a -> Event t (a -> a) -> Event t a
  +
</pre-haskell>
  +
  +
Given an initial value and a time-stream of functions for combining values, this will emit a stream of combined values, accumulating over time. Behold:
  +
  +
<pre-haskell>
  +
counterify :: Event t () -> Event t Integer
  +
counterify ev = accumE 0 (const (+1) <$> ev)
  +
  +
justCount :: IO EventNetwork
  +
justCount = do
  +
let networkDescription :: forall t. Frameworks t => Moment t ()
  +
networkDescription = do
  +
beats <- fromAddHandler (bpmToAddHandler 60)
  +
let counting = counterify beats
  +
reactimate $ fmap print counting
  +
network <- compile networkDescription
  +
actuate network
  +
return network
  +
</pre-haskell>
  +
  +
This will spew numbers into your GHCi prompt, but you can still do the <code-haskell>pause it</code-haskell> thing to stop it counting at you.
  +
  +
== Putting the banana on a diet: scales! ==
  +
  +
You can probably figure this one out yourself:
  +
  +
<pre-haskell>
  +
scale :: Int -> IO EventNetwork
  +
scale bpm = do
  +
let networkDescription :: forall t. Frameworks t => Moment t ()
  +
networkDescription = do
  +
idxE <- counterify <$> fromAddHandler (bpmToAddHandler bpm)
  +
let notesE = (toEnum . ((`mod` 12))) . fromEnum <$> idxE
  +
reactimate $ fmap (uncurry playNote . (negate 5,)) notesE
  +
network <- compile networkDescription
  +
actuate network
  +
return network
  +
</pre-haskell>
  +
  +
For the next one you need to understand reactive-banana's <code-haskell>union</code-haskell> combinator. It just takes two events of the same type and merges them. Then we can do two scales at once!
  +
  +
<pre-haskell>
  +
scales :: Int -> IO EventNetwork
  +
scales bpm = do
  +
let networkDescription :: forall t. Frameworks t => Moment t ()
  +
networkDescription = do
  +
idxAscE <- counterify <$> fromAddHandler (bpmToAddHandler bpm)
  +
let idxDscE = negate <$> idxAscE
  +
notesAscE = (toEnum . ((`mod` 12))) . fromEnum <$> idxAscE
  +
notesDscE = (toEnum . ((`mod` 12))) . fromEnum <$> idxDscE
  +
-- Reactive.Banana.union clashes with Prelude.union, hence RB.union
  +
reactimate $ fmap (uncurry playNote . (negate 5,)) $ RB.union notesAscE notesDscE
  +
network <- compile networkDescription
  +
actuate network
  +
return network
  +
</pre-haskell>
  +
  +
== Non-conclusion ==
  +
  +
That's as far as I'm going for now. Hooking this up to keyboard input would be a logical next step, but I'm off to help my step-family move.

Latest revision as of 22:05, 7 October 2012

Introduction

So I'm writing this tutorial as a means of teaching myself FRP and reactive-banana. It'll probably be full of errors and bad advice, use it at your own risk.

All the tutorials on FRP I've read start with a long boring theory section. This is an instant gratification article. For starters, imagine a man attempting to sharpen a banana into a deadly weapon. See? You're gratified already! Here, I'll write some code for playing musical notes on your computer, attach that to reactive-banana and build increasingly complicated and amusing "sequencers" using it. Now for a boring bit:

Go install sox: <code-bash>apt-get install sox # Or equivalent for your OS/Distro</code-bash>

Get the git repository associated with this tutorial: <code-bash>git clone https://github.com/enolan/rbsttp.git </code-bash>

Install reactive-banana <code-bash>cabal install reactive-banana</code-bash>

Musical interlude

Cd into the git repo and open rbsttp.hs in GHCi:

<pre-bash> cd rbsttp ghci rbsttp.hs </pre-bash>

Now, we can make some beepy noises. Try these:

<pre-haskell> playNote (negate 5) C playNote (negate 5) Fsharp sequence_ . intersperse (threadDelay 1000000) $ map (playNote (negate 5)) [C ..] </pre-haskell>

Play with the value passed to threadDelay a bit for some more interesting noises. It's the time to wait between <code-haskell>Note</code-haskell>s, expresssed in microseconds.

<pre-haskell> sequence_ . intersperse (threadDelay 500000) $ map (playNote (negate 5)) [C ..] sequence_ . intersperse (threadDelay 250000) $ map (playNote (negate 5)) [C ..] sequence_ . intersperse (threadDelay 125000) $ map (playNote (negate 5)) [C ..] sequence_ . intersperse (threadDelay 62500) $ map (playNote (negate 5)) [C ..] </pre-haskell>

You've probably figured out by now that C and Fsharp are data constructors. Here's the definition for my Note type.

<pre-haskell> -- 12 note chromatic scale starting at middle C. data Note =

   C | Csharp | D | Dsharp | E | F | Fsharp | G | Gsharp | A | Asharp | B
   deriving (Show, Enum)

</pre-haskell>

<code-haskell>playNote</code-haskell> is a very hacky synthesizer. It's also asynchronous, which is why <code-haskell>mapM_ playNote (negate 5) [C ..]</code-haskell> doesn't sound too interesting. Here's <code-haskell>playNote</code-haskell>'s type.

<pre-haskell> -- Play a note with a given gain relative to max volume (this should be -- negative), asynchronously. playNote :: Int -> Note -> IO () </pre-haskell>

Ground yourself, then insert the electrodes into the banana

Everything we've done so far is plain old regular Haskell in the IO monad. Try this now:

<pre-haskell> (sendNote, network) <- go1 sendNote ((negate 10), C) sendNote ((negate 10), Fsharp) </pre-haskell>

Congratulations! You just compiled your first <code-haskell>EventNetwork</code-haskell> and sent your first <code-haskell>Event</code-haskell>s. I know this looks like I just made a excessively complicated version of <code-haskell>uncurry playNote</code-haskell>, but bear with me for a moment. Let's look at the code for <code-haskell>go1</code-haskell>:

<pre-haskell> go1 :: IO ((Int, Note) -> IO (), EventNetwork) go1 = do

   (addH, sendNoteEvent) <- newAddHandler
   let networkDescription :: forall t. Frameworks t => Moment t ()
       networkDescription = do
           noteEvent <- fromAddHandler addH
           reactimate $ fmap (uncurry playNote) noteEvent
   network <- compile networkDescription
   actuate network
   return (sendNoteEvent, network)

</pre-haskell>

From it's type we can see that this is an IO action that returns a tuple of what is, yes, just fancy <code-haskell>uncurry playNote</code-haskell> and something called a <code-haskell>EventNetwork</code-haskell>. The <code-haskell>EventNetwork</code-haskell> is the new, interesting bit. The two new important abstractions that reactive-banana introduces are <code-haskell>Event</code-haskell>s and <code-haskell>Behavior</code-haskell>s. <code-haskell>Behavior</code-haskell>s, we'll get to a bit later. <code-haskell>Event</code-haskell>s are values that occur at discrete points in time. You can think of an <code-haskell>Event t a</code-haskell>(ignore the t for now) as a <code-haskell>[(Time, a)]</code-haskell> with the times monotonically increasing as you walk down the list.

In general, to get <code-haskell>Event</code-haskell>s from IO we'll need to use <code-haskell>fromAddHandler</code-haskell>. Unsurprisingly, it wants an <code-haskell>addHandler</code-haskell> as its argument. Let's take a look at those types:

<pre-haskell> type AddHandler a = (a -> IO ()) -> IO (IO ()) fromAddHandler :: Frameworks t => AddHandler a -> Moment t (Event t a) </pre-haskell>

Reactive-banana makes a pretty strong assumption that you're hooking it up to some callback-based, "event driven programming" library. An <code-haskell>AddHandler a takes a function that takes an <code-haskell>a</code-haskell> and does some IO and "registers the callback" and returns a "cleanup" action. Reactive-banana will hook that callback into FRP, and call the cleanup action whenever we <code-haskell>pause</code-haskell> our <code-haskell>EventNetwork</code-haskell>. (You can <code-haskell>pause</code-haskell> and <code-haskell>actuate</code-haskell> an <code-haskell>EventNetwork</code-haskell> as many times as you like.)

Since we don't have anything that looks like an <code-haskell>AddHandler</code-haskell>, we need a convenience function to make one for us. Ta-da:

<pre-haskell> newAddHandler :: IO (AddHandler a, a -> IO ()) </pre-haskell>

That gives us an <code-haskell>AddHandler</code-haskell> and the function that triggers the <code-haskell>Event</code-haskell>, which we bound to the name <code-haskell>sendNote</code-haskell> way back when we ran go1.

<code-haskell>go1</code-haskell> has two <code-haskell>Event</code-haskell>s in it. The first is <code-haskell>noteEvent :: Event t (Int, Note)</code-haskell> the one you send at the ghci prompt. The second is anonymous, but it's type is <code-haskell>Event t (IO ())</code-haskell>. We build that one using <code-haskell>fmap</code-haskell> and <code-haskell>uncurry playNote</code-haskell>. In general, we'll be manipulating <code-haskell>Event</code-haskell>s and <code-haskell>Behavior</code-haskell>s using <code-haskell>fmap</code-haskell>, <code-haskell>Applicative</code-haskell> and some reactive-banana specific combinators.

Put the weird type constraint on <code-haskell>networkDescription</code-haskell> out of your mind for now. The <code-haskell>Moment</code-haskell> monad is what we use to build network descriptions. I don't understand exactly what's going on with <code-haskell> forall Frameworks t. => Moment t ()</code-haskell>, but it makes GHC happy and probably stops me from writing incorrect code somehow.

<code-haskell>compile</code-haskell> turns a network description into an <code-haskell>EventNetwork</code-haskell>, and <code-haskell>actuate</code-haskell> is fancy-FRP-talk for "turn on".

Plug a metronome into the banana

Since GHC has such great concurrency support, and we were already using <code-haskell>threadDelay</code-haskell> back in section 2, we're going to use a couple of threads and a <code-haskell>Chan ()</code-haskell> to build and attach our metronome. Here's a function that lets us build <code-haskell>AddHandler a</code-haskell>s out of IO functions that take <code-haskell>Chan a</code-haskell> as an argument.

<pre-haskell> addHandlerFromThread :: (Chan a -> IO ()) -> AddHandler a addHandlerFromThread writerThread handler = do

   chan <- newChan
   tId1 <- forkIO (writerThread chan)
   tId2 <- forkIO $ forever $ (readChan chan >>= handler)
   return (killThread tId1 >> killThread tId2)

</pre-haskell>

So, basically, we make a new <code-haskell>Chan</code-haskell>, <code-haskell>forkIO</code-haskell> the given function, passing the new <code-haskell>Chan</code-haskell> to it as an argument, create a second thread that triggers the callback handler whenever a new item appears on the <code-haskell>Chan</code-haskell> and returns a cleanup action that kills both threads. Some version of <code-haskell>addHandlerFromThread</code-haskell> may or may not become part of reactive-banana in the future, filing a ticket is on my to-do list.

On to the actual metronome bit:

<pre-haskell> bpmToAddHandler :: Int -> AddHandler () bpmToAddHandler x = addHandlerFromThread go

   where go chan = forever $ writeChan chan () >> threadDelay microsecs
         microsecs :: Int
         microsecs = round $ (1/(fromIntegral x) * 60 * 1000000)

</pre-haskell>

Easy peasy. <code-haskell>goBpm</code-haskell> is basically the same as <code-haskell>go1</code-haskell>, with a different event source and fixed gain and pitch.

<pre-haskell> goBpm :: Int -> IO EventNetwork goBpm bpm = do

   let networkDescription :: forall t. Frameworks t => Moment t ()
       networkDescription = do
           tickEvent <- fromAddHandler (bpmToAddHandler bpm)
           reactimate $ fmap (const $ playNote (negate 5) Fsharp) tickEvent
   network <- compile networkDescription
   actuate network
   return network

</pre-haskell>

Try it out: <pre-haskell> goBpm 240 -- Wait until you get tired of that noise pause it </pre-haskell>

If you've gotten confused here, <code-haskell>it</code-haskell> is a special variable only available in GHCi, holding the return value of the last expression, and <code-haskell>pause</code-haskell> stops the operation of an <code-haskell>EventNetwork</code-haskell>.

Warming things up: Banana, meet Microwave

Let's play some chords instead of just single notes. First, the easy part:

<pre-haskell> -- The last two will sound ugly, but whatever I'm not an actual musician and -- this is a tutorial. chordify :: Note -> [Note] chordify n = let n' = fromEnum n in map (toEnum . (`mod` 12)) [n', n'+1, n'+2] </pre-haskell>

Now how do we hook that up to FRP? We already know fmap, so we can get something of type <code-haskell>Event t Note -> Event t [Note]</code-haskell>, but how do we get a list of <code-haskell>Note</code-haskell>s to play at the same time? Meet a new combinator:

<pre-haskell> spill :: Event t [a] -> Event t a </pre-haskell>

So, now we can define:

<pre-haskell> chordify' :: Event t Note -> Event t Note chordify' = spill . fmap chordify </pre-haskell>

Integrating that into goBpm, we have:

<pre-haskell> goBpmChord :: Int -> IO EventNetwork goBpmChord bpm = do

   let networkDescription :: forall t. Frameworks t => Moment t ()
       networkDescription = do
           tickEvent <- fromAddHandler (bpmToAddHandler bpm)
           let noteEvent = chordify' $ fmap (const C) tickEvent
           reactimate $ fmap (uncurry playNote . (negate 5,)) noteEvent
   network <- compile networkDescription
   actuate network
   return network

</pre-haskell>

This banana is getting crowded! Plugging in a clock

Let's take our metronome and turn it into a beat counting metronome. Then we can play some scales and other patterns - like when we played around with <code-haskell>threadDelay</code-haskell>, <code-haskell>intersperse</code-haskell> and <code-haskell>sequence_</code-haskell> back in section 2. Meet <code-haskell>accumE</code-haskell>:

<pre-haskell> accumE :: a -> Event t (a -> a) -> Event t a </pre-haskell>

Given an initial value and a time-stream of functions for combining values, this will emit a stream of combined values, accumulating over time. Behold:

<pre-haskell> counterify :: Event t () -> Event t Integer counterify ev = accumE 0 (const (+1) <$> ev)

justCount :: IO EventNetwork justCount = do

   let networkDescription :: forall t. Frameworks t => Moment t ()
       networkDescription = do
           beats <- fromAddHandler (bpmToAddHandler 60)
           let counting = counterify beats
           reactimate $ fmap print counting
   network <- compile networkDescription
   actuate network
   return network

</pre-haskell>

This will spew numbers into your GHCi prompt, but you can still do the <code-haskell>pause it</code-haskell> thing to stop it counting at you.

Putting the banana on a diet: scales!

You can probably figure this one out yourself:

<pre-haskell> scale :: Int -> IO EventNetwork scale bpm = do

   let networkDescription :: forall t. Frameworks t => Moment t ()
       networkDescription = do
           idxE <- counterify <$> fromAddHandler (bpmToAddHandler bpm)
           let notesE = (toEnum . ((`mod` 12))) . fromEnum <$> idxE
           reactimate $ fmap (uncurry playNote . (negate 5,)) notesE
   network <- compile networkDescription
   actuate network
   return network

</pre-haskell>

For the next one you need to understand reactive-banana's <code-haskell>union</code-haskell> combinator. It just takes two events of the same type and merges them. Then we can do two scales at once!

<pre-haskell> scales :: Int -> IO EventNetwork scales bpm = do

   let networkDescription :: forall t. Frameworks t => Moment t ()
       networkDescription = do
           idxAscE <- counterify <$> fromAddHandler (bpmToAddHandler bpm)
           let idxDscE = negate <$> idxAscE
               notesAscE = (toEnum . ((`mod` 12))) . fromEnum <$> idxAscE
               notesDscE = (toEnum . ((`mod` 12))) . fromEnum <$> idxDscE
           -- Reactive.Banana.union clashes with Prelude.union, hence RB.union
           reactimate $ fmap (uncurry playNote . (negate 5,)) $ RB.union notesAscE notesDscE
   network <- compile networkDescription
   actuate network
   return network

</pre-haskell>

Non-conclusion

That's as far as I'm going for now. Hooking this up to keyboard input would be a logical next step, but I'm off to help my step-family move.