
Hi all, I wrote a simple interpreter that can be run in the console: data Interaction a b = Exit b | Output b (Interaction a b) | Input (a -> Interaction a b) runConsole :: Interaction String String -> IO () runConsole (Exit b) = putStrLn $ "Finished. Result: " ++ b runConsole (Output s cont) = putStrLn s >> runConsole cont runConsole (Input f) = putStr "> " >> getLine >>= runConsole . f interpreter :: Int -> Interaction String String interpreter i = interaction where interaction = Input input input "exit" = Exit (show i) input "inc" = Output "ok" $ interpreter (i+1) input "show" = Output (show i) interaction input "hello"= Output "Hello World!" interaction input s = Output ("Whas's '" ++ s ++ "' ?") interaction main = runConsole . Output "Known commands: show, inc, hello, exit" $ interpreter 5 I have not yet gained a good understanding of the continuation monad, but I wonder if it could be used here. What would a clean solution look like? Perhaps there are other things that need to be changed as well? Regards, Tim

On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner
I have not yet gained a good understanding of the continuation monad, but I wonder if it could be used here. What would a clean solution look like? Perhaps there are other things that need to be changed as well?
Your 'Interaction' data type is actually an instance of the more general "operational monad" (as named by Heinrich Apfelmus) or "prompt monad" (as named by Ryan Ingram). You will ready-to-use implementations on the packages MonadPrompt [1] and operational [2,3]. Reading their documentation you'll find some links about the development of these concepts. MonadPrompt uses a Cont-style implementation, while operational uses a simple abstract data type together with a viewing function that avoids O(n²) behavior. If you find it hard to describe your 'Interaction' using operational (easiest to use package, IMO), please send us another e-mail. Cheers! [1] http://hackage.haskell.org/package/MonadPrompt [2] http://hackage.haskell.org/package/operational [3] http://heinrichapfelmus.github.com/operational/Documentation.html -- Felipe.

Thanks a lot! Althaugh I have some understanding of the Haskell basics and
the most important monads, I feel that I have to see more well designed
code in order to become a good Haskeller. Can somebody make suggestions
what materials are best to work through in order to achieve this? Are there
easy research papers about Haskell programming? Or should I try the
Monad.Reader? I'm looking for topics that either can be used directly in
many situations or that show some functional principles that boost my
creativity and functional thinking.
Regards,
Tim
2011/11/19 Felipe Almeida Lessa
On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner
wrote: I have not yet gained a good understanding of the continuation monad, but I wonder if it could be used here. What would a clean solution look like? Perhaps there are other things that need to be changed as well?
Your 'Interaction' data type is actually an instance of the more general "operational monad" (as named by Heinrich Apfelmus) or "prompt monad" (as named by Ryan Ingram). You will ready-to-use implementations on the packages MonadPrompt [1] and operational [2,3]. Reading their documentation you'll find some links about the development of these concepts. MonadPrompt uses a Cont-style implementation, while operational uses a simple abstract data type together with a viewing function that avoids O(n²) behavior.
If you find it hard to describe your 'Interaction' using operational (easiest to use package, IMO), please send us another e-mail.
Cheers!
[1] http://hackage.haskell.org/package/MonadPrompt [2] http://hackage.haskell.org/package/operational [3] http://heinrichapfelmus.github.com/operational/Documentation.html
-- Felipe.

Tim Baumgartner wrote:
Thanks a lot! Althaugh I have some understanding of the Haskell basics and the most important monads, I feel that I have to see more well designed code in order to become a good Haskeller. Can somebody make suggestions what materials are best to work through in order to achieve this? Are there easy research papers about Haskell programming? Or should I try the Monad.Reader? I'm looking for topics that either can be used directly in many situations or that show some functional principles that boost my creativity and functional thinking.
You may want to start with the Functional Pearls http://www.haskell.org/haskellwiki/Research_papers/Functional_pearls In particular, I recommend * Richard Bird. A program to solve Sudoku. * Graham Hutton. The countdown problem. * Martin Erwig and Steve Kollmansberger. Probabilistic functional programming in Haskell. * Conor McBride and Ross Paterson. Applicative Programming with Effects. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

I've read Martin Erwig and Steve Kollmansberger's *Probabilistic functional
programming in Haskell*.
Does someone know if the library they are talking about is available on
hackage?
2011/11/21 Heinrich Apfelmus
Tim Baumgartner wrote:
Thanks a lot! Althaugh I have some understanding of the Haskell basics and the most important monads, I feel that I have to see more well designed code in order to become a good Haskeller. Can somebody make suggestions what materials are best to work through in order to achieve this? Are there easy research papers about Haskell programming? Or should I try the Monad.Reader? I'm looking for topics that either can be used directly in many situations or that show some functional principles that boost my creativity and functional thinking.
You may want to start with the Functional Pearls
http://www.haskell.org/**haskellwiki/Research_papers/**Functional_pearlshttp://www.haskell.org/haskellwiki/Research_papers/Functional_pearls
In particular, I recommend
* Richard Bird. A program to solve Sudoku. * Graham Hutton. The countdown problem. * Martin Erwig and Steve Kollmansberger. Probabilistic functional programming in Haskell. * Conor McBride and Ross Paterson. Applicative Programming with Effects.
Best regards, Heinrich Apfelmus
-- http://apfelmus.nfshost.com
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

On 21 November 2011 14:48, Yves Parès
I've read Martin Erwig and Steve Kollmansberger's Probabilistic functional programming in Haskell. Does someone know if the library they are talking about is available on hackage?
Henning Thielemann has a "batteries included" version on Hackage: http://hackage.haskell.org/package/probability I'd expect the original (micro) library is still available from Martin Erwig's website.

Hi Heinrich,
I read your article about the operational monad and found it really very
enlightening. So I'm curious to work through the material you linked below.
Thanks!
Regards
Tim
2011/11/21 Heinrich Apfelmus
Tim Baumgartner wrote:
Thanks a lot! Althaugh I have some understanding of the Haskell basics and the most important monads, I feel that I have to see more well designed code in order to become a good Haskeller. Can somebody make suggestions what materials are best to work through in order to achieve this? Are there easy research papers about Haskell programming? Or should I try the Monad.Reader? I'm looking for topics that either can be used directly in many situations or that show some functional principles that boost my creativity and functional thinking.
You may want to start with the Functional Pearls
http://www.haskell.org/**haskellwiki/Research_papers/**Functional_pearlshttp://www.haskell.org/haskellwiki/Research_papers/Functional_pearls
In particular, I recommend
* Richard Bird. A program to solve Sudoku. * Graham Hutton. The countdown problem. * Martin Erwig and Steve Kollmansberger. Probabilistic functional programming in Haskell. * Conor McBride and Ross Paterson. Applicative Programming with Effects.
Best regards, Heinrich Apfelmus
-- http://apfelmus.nfshost.com
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Nov 19, 2011 at 3:29 PM, Felipe Almeida Lessa
On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner
wrote: I have not yet gained a good understanding of the continuation monad, but I wonder if it could be used here. What would a clean solution look like? Perhaps there are other things that need to be changed as well?
Your 'Interaction' data type is actually an instance of the more general "operational monad" (as named by Heinrich Apfelmus) or "prompt monad" (as named by Ryan Ingram).
Both of which are just disguised free monads. For reference:
data Free f a = Val a | Wrap (f (Free f a))
foldFree :: Functor f => (a -> b) -> (f b -> b) -> Free f a -> b
foldFree v w (Val a) = v a
foldFree v w (Wrap t) = w $ fmap (foldFree v w) t
instance Functor f => Monad (Free f) where
return = Val
m >>= f = foldFree f Wrap m
To use Free, just find the signature functor for Interaction by
replacing the recursive instances with a new type variable,
data InteractionF a b x = ExitF b
| OutputF b x
| InputF (a -> x)
instance Functor (InteractionF a b) where
fmap f (ExitF b) = ExitF b
fmap f (OutputF b x) = OutputF b (f x)
fmap f (InputF g) = InputF (f . g)
roll :: InteractionF a b (Interaction a b) -> Interaction a b
roll (ExitF b) = Exit b
roll (OutputF b x) = Output b x
roll (InputF g) = Input g
type InteractionM a b = Free (InteractionF a b)
runM :: InteractionM a b b -> Interaction a b
runM = foldFree Exit roll
exit :: b -> InteractionM a b c
exit b = Wrap (ExitF b)
output :: b -> InteractionM a b ()
output b = Wrap (OutputF b (Val ()))
input :: InteractionM a b a
input = Wrap (InputF Val)
--
Dave Menendez

Free Monads. It's amazing to be confronted again with notions I learned
more than ten years ago for groups. I have to admit that I'm probably not
yet prepared for a deeper understanding of this, but hopefully I will
return to it later ;-)
Is Cont free as well? I guess so because I heard it's sometimes called the
mother of all monads.
Regards
Tim
2011/11/21 David Menendez
On Sat, Nov 19, 2011 at 3:29 PM, Felipe Almeida Lessa
wrote: On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner
wrote: I have not yet gained a good understanding of the continuation monad, but I wonder if it could be used here. What would a clean solution look like? Perhaps there are other things that need to be changed as well?
Your 'Interaction' data type is actually an instance of the more general "operational monad" (as named by Heinrich Apfelmus) or "prompt monad" (as named by Ryan Ingram).
Both of which are just disguised free monads. For reference:
data Free f a = Val a | Wrap (f (Free f a))
foldFree :: Functor f => (a -> b) -> (f b -> b) -> Free f a -> b foldFree v w (Val a) = v a foldFree v w (Wrap t) = w $ fmap (foldFree v w) t
instance Functor f => Monad (Free f) where return = Val m >>= f = foldFree f Wrap m
To use Free, just find the signature functor for Interaction by replacing the recursive instances with a new type variable,
data InteractionF a b x = ExitF b | OutputF b x | InputF (a -> x)
instance Functor (InteractionF a b) where fmap f (ExitF b) = ExitF b fmap f (OutputF b x) = OutputF b (f x) fmap f (InputF g) = InputF (f . g)
roll :: InteractionF a b (Interaction a b) -> Interaction a b roll (ExitF b) = Exit b roll (OutputF b x) = Output b x roll (InputF g) = Input g
type InteractionM a b = Free (InteractionF a b)
runM :: InteractionM a b b -> Interaction a b runM = foldFree Exit roll
exit :: b -> InteractionM a b c exit b = Wrap (ExitF b)
output :: b -> InteractionM a b () output b = Wrap (OutputF b (Val ()))
input :: InteractionM a b a input = Wrap (InputF Val)
-- Dave Menendez
http://www.eyrie.org/~zednenem/

On Mon, Nov 21, 2011 at 2:13 PM, Tim Baumgartner
Free Monads. It's amazing to be confronted again with notions I learned more than ten years ago for groups. I have to admit that I'm probably not yet prepared for a deeper understanding of this, but hopefully I will return to it later ;-) Is Cont free as well? I guess so because I heard it's sometimes called the mother of all monads.
As I understand it, Cont is not a free monad, but there is a
connection between the ideas. Certainly, any free monad can be easily
reimplemented using Cont.
Here's how you might implement your monad using Cont,
type InteractionM a b = Cont (Interaction a b)
exit b = Cont $ \k -> Exit b
output b = Cont $ \k -> Output b (k ())
input = Cont $ \k -> Input k
runM m = runCont m Exit
That's very similar to the free monad's implementation, only with the
continuation replacing Val.
exit b = Wrap $ ExitF b
output b = Wrap $ OutputF b (Val ())
input = Wrap $ InputF Val
runM m = foldFree Exit roll m
The Cont-based version has essentially taken the work performed in
foldFree and distributed it to return and (>>=). This eliminates the
intermediate data structures, resulting in a more efficient
implementation.
--
Dave Menendez

2011/11/21 David Menendez
Here's how you might implement your monad using Cont,
type InteractionM a b = Cont (Interaction a b)
exit b = Cont $ \k -> Exit b output b = Cont $ \k -> Output b (k ()) input = Cont $ \k -> Input k runM m = runCont m Exit
That's what I originally wanted to know. I guess I struggled with the definition of output. Oh, there's so much more to learn... Thanks, Tim

You'll probably get answers from people who are more proficient with this, but here's what I learned over the years. Tim Baumgartner wrote:
Is Cont free as well?
No. In fact, free monads are quite a special case, many monads are not free, e.g. the list monad. I believe what David Menendez said was meant to mean 'modulo some equivalence relation' i.e. you can define/implement many monads as 'quotients' of a free monad. But you cannot do this with Cont (though I am not able to give a proof).
I guess so because I heard it's sometimes called the mother of all monads.
It is, in the sense that you can implement all monads in terms of Cont. Cheers Ben
participants (7)
-
Ben Franksen
-
David Menendez
-
Felipe Almeida Lessa
-
Heinrich Apfelmus
-
Stephen Tetley
-
Tim Baumgartner
-
Yves Parès