[Haskell-cafe] What pattern is this (Something.T -> IO a) in Sound.ALSA.Sequencer

Roman Cheplyaka roma at ro-che.info
Sun Mar 3 21:11:21 CET 2013


Hi Martin,

These are called "continuations" or "callbacks". In this case, the term
"callback" seems to fit better, since the result of continuation is an
IO action.

The common use case for callbacks is when you want to release some
resources after the IO action completes. Let's look at the definition of
withSimple:

  withSimple ::
     Seq.T mode -> String -> Port.Cap -> Port.Type ->
     (Port.T -> IO a) ->
     IO a
  withSimple ss s c t =
     bracket (createSimple ss s c t) (deleteSimple ss)

It uses the 'bracket' function (from Control.Exception) to acquire resource,
run the given IO action with that resource and release the resource
afterwards. An important property of bracket is that it is exception-safe:
resources will be released even when the supplied action throws an
exception. But ignoring exceptions, withSimple is equivalent to

  withSimple ss s c t callback = do
    port <- createSimple ss s c t
    callback port
    deleteSimple ss port

The non-callback version of withSimple is createSimple, which returns
the Port itself. But it doesn't release the Port afterwards, because it
has no way to know when you've finished working with it.

Callbacks can often be found in imperative programming.
Almost all GUI libraries and some I/O frameworks (notably, node.js) are
based on callbacks.

Admittedly, programming with callbacks is not very pleasant. So we have
an excellent alternative — the continuation monad transformer!

This nested code

  something1 $ \x -> do
          something2 $ \y -> do
                  something3 $ \z -> do

can be equivalently rewritten as this linear code

  import Control.Monad.Cont

  flip runContT return $ do
    x <- ContT something1
    y <- ContT something2
    z <- ContT something3
    lift $ do
      ...

Notice that we completely change the style of interaction with the
library without changing the library itself at all!

For a complete example you can look at the ValueGetter monad in the
test-framework-golden package.

Roman

* Martin Drautzburg <Martin.Drautzburg at web.de> [2013-03-03 19:28:39+0100]
> Hello all,
> 
> this was previously posted on Haskell Beginners, but only partially answered.
> 
> In Sound.ALSA.Sequencer, there are a number of functions which together set up 
> a midi environement (client, port, queue). They all have a type, where the 
> last argument has a type like:
> 
> (something.T -> IO a)
> 
> i.e.
> 
> *Main> :t SndSeq.withDefault
> SndSeq.withDefault
>   :: SndSeq.OpenMode mode =>
>      SndSeq.BlockMode -> (SndSeq.T mode -> IO a) -> IO a
> 
> *Main> :t Port.withSimple
> Port.withSimple
>   :: SndSeq.T mode
>      -> String -> Port.Cap -> Port.Type -> (Port.T -> IO a) -> IO a
> 
> *Main> :t Queue.with
> Queue.with :: SndSeq.T mode -> (Queue.T -> IO a) -> IO a
> 
> There is example code, where a full setup is created by a number of nested 
> "do" blocks. The repeating pattern there is:
> 
> something1 $ \x -> do
>         something2 $ \y -> do
>                 something3 $ \z -> do
> 
> 
> What is this all about? I particularly would like to understand, when this 
> parttern is needed and what determines the the number of nested "do" blocks. 
> 
> -- 
> Martin
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list