Building a monoid, continuation-passing style

Hello cafe, Inspired by Sean Leather's xformat package [1] I built a datatype with which you can build a monoid with holes, yielding a function type to fill in these holes, continuation-passing style. Here are some primitives and their types:
now :: m -> ContSt m r r later :: (a -> m) -> ContSt m r (a -> r) run :: ContSt m m r -> r instance Monoid m => Category (ContSt m)
Here's an example of how to use it:
run (now "hello" . now "world") "helloworld"
run (later id . now "world") "hello" "helloworld"
run (later id . later show) "hello" 567 "hello567"
The source code is available at [2]. I have a couple of questions: * ContSt is a Category. Is it also an Arrow? Why (not)? * Did I miss any other obvious classes this type is an instance of? * What is its relation with the Cont and Reader monads? * Are there any other useful applications other than printf-like functionality? * ContSt is a horrible name. What is a better one? For those who have a bit more time: I appreciate any comments and suggestions on the code. :-) Many thanks in advance, Martijn. [1] http://hackage.haskell.org/package/xformat [2] http://code.google.com/p/monoid-cont/source/browse/trunk/ContSt.hs

On Mon, Sep 14, 2009 at 11:25 AM, Martijn van Steenbergen
Inspired by Sean Leather's xformat package [1] I built a datatype with which you can build a monoid with holes, yielding a function type to fill in these holes, continuation-passing style.
Neat!
I have a couple of questions: * ContSt is a Category. Is it also an Arrow? Why (not)?
I think it isn't. To be an Arrow, you need a definition for first, and to write first you need to be able to transform a function of type f r -> a into a function of type f (r,b) -> (a,b), which I'm pretty sure is impossible.
* What is its relation with the Cont and Reader monads?
I'm reminded of the parameterized monad of continuations that Oleg mentioned a few years back. http://www.haskell.org/pipermail/haskell/2007-December/020034.html Here's one way of expressing it: class Paramonad m where ret :: a -> m x x a bind :: m x y a -> (a -> m y z b) -> m x z b liftP2 :: (Paramonad m) => (a -> b -> c) -> m x y a -> m y z b -> m x z c liftP2 (*) m1 m2 = m1 `bind` \a -> m2 `bind` \b -> ret (a * b) newtype Cont x y a = Cont { runCont :: (a -> y) -> x } run :: Cont x a a -> x run m = runCont m id instance Paramonad Cont where ret a = Cont $ \k -> k a m `bind` f = Cont $ \k -> runCont m (\a -> runCont (f a) k) shift :: ((a -> Cont z z y) -> Cont x b b) -> Cont x y a shift f = Cont $ \k -> run $ f (ret . k) (<>) :: Monoid m => Cont x y m -> Cont y z m -> Cont x z m (<>) = liftP2 mappend later :: (a -> m) -> Cont (a -> r) r m later f = shift $ \k -> ret (run . k . f) -- equivalently, -- later f = Cont $ \k -> k . f
run (ret "x" <> ret "y") "xy"
run (ret "x" <> later id) "y" "xy"
and so forth. In fact, this is a good candidate for an alternative implementation. newtype ContSt m r a = ContSt (Cont a r m) It would be interesting to compare their relative efficiency.
* ContSt is a horrible name. What is a better one?
HoleyMonoid?
--
Dave Menendez

David Menendez wrote:
I'm reminded of the parameterized monad of continuations that Oleg mentioned a few years back.
http://www.haskell.org/pipermail/haskell/2007-December/020034.html
This is all very interesting, thank you both for the pointers! I was trying to get rid of the newtypes but couldn't think of how to do that. I can't believe the solution now is as simple as (m -> r) -> a. There's hardly any code left, now. The fact that it all exists already is nice on the one hand and sad on the other. :-) I will have to look into parametrized monads and parametrized applicatives. Thanks again, Martijn.

For reference Oleg's indexed continuation monad is packaged on hackage in category-extras as: http://hackage.haskell.org/packages/archive/category-extras/latest/doc/html/... -Edward Kmett On Wed, Sep 16, 2009 at 7:07 AM, Martijn van Steenbergen < martijn@van.steenbergen.nl> wrote:
David Menendez wrote:
I'm reminded of the parameterized monad of continuations that Oleg mentioned a few years back.
http://www.haskell.org/pipermail/haskell/2007-December/020034.html
This is all very interesting, thank you both for the pointers!
I was trying to get rid of the newtypes but couldn't think of how to do that. I can't believe the solution now is as simple as (m -> r) -> a. There's hardly any code left, now.
The fact that it all exists already is nice on the one hand and sad on the other. :-)
I will have to look into parametrized monads and parametrized applicatives.
Thanks again,
Martijn.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Sep 14, 2009 at 10:25 AM, Martijn van Steenbergen
Hello cafe,
Inspired by Sean Leather's xformat package [1] I built a datatype with which you can build a monoid with holes, yielding a function type to fill in these holes, continuation-passing style. Here are some primitives and their types:
now :: m -> ContSt m r r later :: (a -> m) -> ContSt m r (a -> r) run :: ContSt m m r -> r instance Monoid m => Category (ContSt m)
Here's an example of how to use it:
run (now "hello" . now "world")
"helloworld"
run (later id . now "world") "hello"
"helloworld"
run (later id . later show) "hello" 567
"hello567"
The source code is available at [2].
I have a couple of questions: * ContSt is a Category. Is it also an Arrow? Why (not)? * Did I miss any other obvious classes this type is an instance of? * What is its relation with the Cont and Reader monads? * Are there any other useful applications other than printf-like functionality? * ContSt is a horrible name. What is a better one?
For those who have a bit more time: I appreciate any comments and suggestions on the code. :-)
I believe this technique is based on a technique introduced in Olivier Danvy's "Functional Unparsing". While not immediately applicable to Haskell unless you want to make/use a delimited continuation monad, you may find the paper "On Typing Delimited Continuations: Three New Solutions to the Printf Problem" by Kenichi Asai interesting. It is available at the following url: http://pllab.is.ocha.ac.jp/~asai/papers/papers.html
participants (4)
-
David Menendez
-
Derek Elkins
-
Edward Kmett
-
Martijn van Steenbergen