What pattern is this (Something.T -> IO a) in Sound.ALSA.Sequencer
 
            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
 
            On Sun, Mar 3, 2013 at 10:28 AM, Martin Drautzburg  wrote: 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) These things are in the Kleisli category for IO.  In short, an argument
with this type is a function which makes an IO action.  The function which
takes one of these as an action "knows" how to get a "something.T" to apply
to the function, either because it is an argument to the bigger function,
or because the library author knows the monad has an action with the type
IO (something.T).
This is safer than passing around unconstrained IO actions.  For example,
consider: outer :: String -> (Int -> IO ()) -> IO ()
versus
outer :: String -> IO () -> IO () The second type requires that the library user can construct an appropriate
IO () action, and the intended dependence on the Int is not statically
verified.  On the other hand, the first type requires that you pass in an
IO () action constructor that explicitly depends on an Int.  The "only" way
you can drop the dependence on the Int is if you explicitly ignore it (and
you can turn on warnings to catch that kind of thing) 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. It can be refactored, so it is never "needed".  On the other hand, it does
have nice properties.  The x,y, z variables are all in scope when you're in
something3's do-block argument.
The determining factor in the nesting depth is how many actions which take
elements of a Kliesli category for the monad will be sequenced, since each
one requires its own lambda-do-block.
 
            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 
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
 
            On Sunday, 3. March 2013 21:11:21 Roman Cheplyaka wrote:
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 ...
Mind-blowing. Thanks a lot. Before I dig into the continuation monad transformer, one more question (demonstrating my ignorance): The initialization actually starts with main = (do SndSeq.withDefault SndSeq.Block $ \h -> do Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" Port.withSimple h "out" (Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) $ \p -> do So there are some plain actions like "Client.setName" and "Port.withSimple" before it gets to the next "do" block. How would I write this in ContT style? -- Martin
 
            * Martin Drautzburg 
On Sunday, 3. March 2013 21:11:21 Roman Cheplyaka wrote:
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 ...
Mind-blowing. Thanks a lot. Before I dig into the continuation monad transformer, one more question (demonstrating my ignorance):
The initialization actually starts with
main = (do SndSeq.withDefault SndSeq.Block $ \h -> do Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" Port.withSimple h "out" (Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) $ \p -> do
So there are some plain actions like "Client.setName" and "Port.withSimple" before it gets to the next "do" block. How would I write this in ContT style?
You can use the "lift" function to lift actions from the underlying monad to the transformer. In your case it'd be something like flip runContT return $ do h <- ContT $ SndSeq.withDefault SndSeq.Block lift $ Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" p <- ContT $ Port.withSimple h "out" (Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) ... Roman
participants (3)
- 
                 Alexander Solla Alexander Solla
- 
                 Martin Drautzburg Martin Drautzburg
- 
                 Roman Cheplyaka Roman Cheplyaka