Domanda

While hacking something up earlier, I created the following code:

newtype Callback a = Callback { unCallback :: a -> IO (Callback a) }

liftCallback :: (a -> IO ()) -> Callback a
liftCallback f = let cb = Callback $ \x -> (f x >> return cb) in cb

runCallback :: Callback a -> IO (a -> IO ())
runCallback cb =
    do ref <- newIORef cb
       return $ \x -> readIORef ref >>= ($ x) . unCallback >>= writeIORef ref

Callback a represents a function that handles some data and returns a new callback that should be used for the next notification. A callback which can basically replace itself, so to speak. liftCallback just lifts a normal function to my type, while runCallback uses an IORef to convert a Callback to a simple function.

The general structure of the type is:

data T m a = T (a -> m (T m a))

It looks much like this could be isomorphic to some well-known mathematical structure from category theory.

But what is it? Is it a monad or something? An applicative functor? A transformed monad? An arrow, even? Is there a search engine similar Hoogle that lets me search for general patterns like this?

È stato utile?

Soluzione

The term you are looking for is free monad transformer. The best place to learn how these work is to read the "Coroutine Pipelines" article in issue 19 of The Monad Reader. Mario Blazevic gives a very lucid description of how this type works, except he calls it the "Coroutine" type.

I wrote up his type in the transformers-free package and then it got merged into the free package, which is its new official home.

Your Callback type is isomorphic to:

type Callback a = forall r . FreeT ((->) a) IO r

To understand free monad transformers, you need to first understand free monads, which are just abstract syntax trees. You give the free monad a functor which defines a single step in the syntax tree, and then it creates a Monad from that Functor that is basically a list of those types of steps. So if you had:

Free ((->) a) r

That would be a syntax tree that accepts zero or more as as input and then returns a value r.

However, usually we want to embed effects or make the next step of the syntax tree dependent on some effect. To do that, we simply promote our free monad to a free monad transformer, which interleaves the base monad between syntax tree steps. In the case of your Callback type, you are interleaving IO in between each input step, so your base monad is IO:

FreeT ((->) a) IO r

The nice thing about free monads is that they are automatically monads for any functor, so we can take advantage of this to use do notation to assemble our syntax tree. For example, I can define an await command that will bind the input within the monad:

import Control.Monad.Trans.Free

await :: (Monad m) => FreeT ((->) a) m a
await = liftF id

Now I have a DSL for writing Callbacks:

import Control.Monad
import Control.Monad.Trans.Free

printer :: (Show a) => FreeT ((->) a) IO r
printer = forever $ do
    a <- await
    lift $ print a

Notice that I never had to define the necessary Monad instance. Both FreeT f and Free f are automatically Monads for any functor f, and in this case ((->) a) is our functor, so it automatically does the right thing. That's the magic of category theory!

Also, we never had to define a MonadTrans instance in order to use lift. FreeT f is automatically a monad transformer, given any functor f, so it took care of that for us, too.

Our printer is a suitable Callback, so we can feed it values just by deconstructing the free monad transformer:

feed :: [a] -> FreeT ((->) a) IO r -> IO ()
feed as callback = do
    x <- runFreeT callback
    case x of
        Pure _ -> return ()
        Free k -> case as of
            []   -> return ()
            b:bs -> feed bs (k b)

The actual printing occurs when we bind runFreeT callback, which then gives us the next step in the syntax tree, which we feed the next element of the list.

Let's try it:

>>> feed [1..5] printer
1
2
3
4
5

However, you don't even need to write all this up yourself. As Petr pointed out, my pipes library abstracts common streaming patterns like this for you. Your callback is just:

forall r . Consumer a IO r

The way we'd define printer using pipes is:

printer = forever $ do
    a <- await
    lift $ print a

... and we can feed it a list of values like so:

>>> runEffect $ each [1..5] >-> printer
1
2
3
4
5

I designed pipes to encompass a very large range of streaming abstractions like these in such a way that you can always use do notation to build each streaming component. pipes also comes with a wide variety of elegant solutions for things like state and error handling, and bidirectional flow of information, so if you formulate your Callback abstraction in terms of pipes, you tap into a ton of useful machinery for free.

If you want to learn more about pipes, I recommend you read the tutorial.

Altri suggerimenti

The general structure of the type looks to me like

data T (~>) a = T (a ~> T (~>) a)

where (~>) = Kleisli m in your terms (an arrow).


Callback itself doesn't look like an instance of any standard Haskell typeclass I can think of, but it is a Contravariant Functor (also known as Cofunctor, misleadingly as it turns out). As it is not included in any of the libraries that come with GHC, there exist several definitions of it on Hackage (use this one), but they all look something like this:

class Contravariant f where
    contramap :: (b -> a) -> f a -> f b
 -- c.f. fmap :: (a -> b) -> f a -> f b

Then

instance Contravariant Callback where
    contramap f (Callback k) = Callback ((fmap . liftM . contramap) f (f . k))

Is there some more exotic structure from category theory that Callback possesses? I don't know.

I think that this type is very close to what I have heard called a 'Circuit', which is a type of arrow. Ignoring for a moment the IO part (as we can have this just by transforming a Kliesli arrow) the circuit transformer is:

newtype CircuitT a b c = CircuitT { unCircuitT :: a b (c, CircuitT a b c) }

This is basicall an arrow that returns a new arrow to use for the next input each time. All of the common arrow classes (including loop) can be implemented for this arrow transformer as long as the base arrow supports them. Now, all we have to do to make it notionally the same as the type you mention is to get rid of that extra output. This is easily done, and so we find:

Callback a ~=~ CircuitT (Kleisli IO) a ()

As if we look at the right hand side:

CircuitT (Kleisli IO) a () ~=~
  (Kliesli IO) a ((), CircuitT (Kleisli IO) a ()) ~=~
  a -> IO ((), CircuitT (Kliesli IO) a ())

And from here, you can see how this is similar to Callback a, except we also output a unit value. As the unit value is in a tuple with something else anyway, this really doesn't tell us much, so I would say they're basically the same.

N.B. I used ~=~ for similar but not entirely equivalent to, for some reason. They are very closely similar though, in particular note that we could convert a Callback a into a CircuitT (Kleisli IO) a () and vice-versa.

EDIT: I would also fully agree with the ideas that this is A) a monadic costream (monadic operation expecitng an infinite number of values, I think this means) and B) a consume-only pipe (which is in many ways very similar to the circuit type with no output, or rather output set to (), as such a pipe could also have had output).

Just an observation, your type seems quite related to Consumer p a m appearing in the pipes library (and probably other similar librarties as well):

type Consumer p a = p () a () C
-- A Pipe that consumes values
-- Consumers never respond.

where C is an empty data type and p is an instance of Proxy type class. It consumes values of type a and never produces any (because its output type is empty).

For example, we could convert a Callback into a Consumer:

import Control.Proxy
import Control.Proxy.Synonym

newtype Callback m a = Callback { unCallback :: a -> m (Callback m a) }

-- No values produced, hence the polymorphic return type `r`.
-- We could replace `r` with `C` as well.
consumer :: (Proxy p, Monad m) => Callback m a -> () -> Consumer p a m r
consumer c () = runIdentityP (run c)
  where
    run (Callback c) = request () >>= lift . c >>= run

See the tutorial.

(This should have been rather a comment, but it's a bit too long.)

Autorizzato sotto: CC-BY-SA insieme a attribuzione
Non affiliato a StackOverflow
scroll top