
(This e-mail is a literate Haskell file.) Ryan Ingram enlightened us with MonadPrompt as a very nice abstraction for turn-based games, allowing easy programming and testing. http://www.mail-archive.com/haskell-cafe@haskell.org/msg33040.html http://ryani.freeshell.org/haskell/ I wonder how nicely it fits on a Gtk2Hs application. =)
{-# OPTIONS_GHC -fglasgow-exts -Wall #-} import Control.Concurrent import Control.Concurrent.MVar import Control.Monad import Control.Monad.Fix import Graphics.UI.Gtk import System.IO import System.Random
Needed for the GADTs and some type signatures. (yes, I'm stuck with GHC 6.6.1 for now =/ ) While you read the e-mail, choose the appropriate main function
main :: IO () main = consoleMain -- main = gtkApp forkAttempt -- main = gtkApp subLoopAttempt -- main = gtkApp lastAttempt
For the purposes of this e-mail, I'll present here a simplified version of his MonadPrompt:
class Monad m => MonadPrompt p m | m -> p where prompt :: p a -> m a
data Prompt (p :: * -> *) r where PromptDone :: r -> Prompt p r Prompt :: p a -> (a -> Prompt p r) -> Prompt p r
instance Monad (Prompt p) where return = PromptDone PromptDone x >>= f = f x Prompt p cont >>= f = Prompt p ((>>= f) . cont)
instance MonadPrompt p (Prompt p) where prompt p = Prompt p return
With the monad above, we may program a simple guessing game. This is based on http://ryani.freeshell.org/haskell/Main.lhs and you can do every analysis done here with his sources, but I'm again trying to keep everything as simple as possible.
guessGame :: MonadPrompt GuessP m => Int -> m Int guessGame answer = guessMe 1 where guessMe tries = do prompt (Print $ "Guess #" ++ show tries ++ ":") guess <- prompt Guess if guess == answer then do prompt (Print "Right!") return tries else do prompt (Print $ "You guessed too " ++ if guess < answer then "low" else "high" ++ "! Try again.") guessMe (tries + 1)
Okay, so our game do prompts over the GuessP data type,
data GuessP a where
where you may ask the user for a guess
Guess :: GuessP Int
or you may show him some info about the game.
Print :: String -> GuessP ()
To play our little game, we have to execute the Prompt. We have
runPromptM :: Monad m => (forall a. p a -> m a) -> Prompt p r -> m r runPromptM _ (PromptDone result) = return result runPromptM f (Prompt p cont) = f p >>= runPromptM f . cont
which basically maps prompts to actions on some monad -- in particular, IO. Doing a console interface isn't hard at all:
consolePrompt :: forall a. GuessP a -> IO a consolePrompt (Print s) = putStrLn s consolePrompt Guess = fmap read getLine
guessGameNew :: MonadPrompt GuessP m => IO (m Int) guessGameNew = randomRIO (1, 10) >>= return . guessGame
consoleMain :: IO () consoleMain = do hSetBuffering stdout NoBuffering game <- guessGameNew attempts <- runPromptM consolePrompt game putStrLn $ "You took " ++ show attempts ++ " attempts."
That's really cool =). However, mapping runPromptM into a Gtk2Hs application isn't easy at all (we'll see why shortly). Before that, let's take the common blocks of code away. All of our attempts will develop a function that takes a function for showing info, an entry for reading guesses and a button that will be clicked to make the guess.
type AttemptCode = (String -> IO ()) -> Entry -> Button -> IO ()
gtkApp :: AttemptCode -> IO () gtkApp run = do unsafeInitGUIForThreadedRTS -- allows runghc w <- windowNew w `onDestroy` mainQuit container <- vBoxNew False 7 w `containerAdd` container
let showInfo info = do m <- messageDialogNew (Just w) [] MessageInfo ButtonsOk info dialogRun m >> widgetDestroy m
entry <- entryNew boxPackStart container entry PackNatural 0
button <- buttonNewWithLabel "Guess" boxPackStart container button PackNatural 0
widgetShowAll w timeoutAdd (run showInfo entry button >> return False) 0 mainGUI
With everything in place, let's start! The first naïve attempt would be to just connect every point
{- naïveAttempt :: AttemptCode naïveAttempt showInfo entry button = do game <- guessGameNew let mapping (Print s) = showInfo s mapping Guess = -- Oops -}
It's easy to see that we can't get the guess from our user using a function like 'getLine'. The problem lies in the fact that Gtk is event-driven, so every time we ask the user for something, we have to wait for the corresponding event that will bring us his answer. 'runPromptM' basically creates one big monolithic monad that will run from the beginning to the end of the game -- exactly the same thing 'mainGUI' does! The standard way of solving the problem of running two sequential things at once is using threads, and this solution is specially appealing since Control.Concurrent simplifies the matters *a lot*. So let's try this instead
forkAttempt :: AttemptCode forkAttempt showInfo entry button = do game <- guessGameNew forkIO $ do attempts <- runPromptM forkedMapping game postGUIAsync (showInfo $ "You took " ++ show attempts ++ " attempts.") return () where forkedMapping :: forall a. GuessP a -> IO a forkedMapping (Print s) = postGUIAsync (showInfo s) forkedMapping Guess = do v <- newEmptyMVar cid <- postGUISync $ onClicked button $ entryGetText entry >>= putMVar v guess <- takeMVar v -- f1 postGUISync (signalDisconnect cid) -- f2 return (read guess)
Problem solved? Not really: - This kind of implementation hides lots of subtle bugs. For example, because of postGUIAsync being used in Print case, the user will see multiple dialog boxes at once and -- strangely enough -- he'll see first the last message printed. It isn't always easy to see this kind of bug at first sight, and it can be very hard to track it down. - Another problem may happen with scheduling. For some reason, there are times in which it takes some time for the control to pass from the Gtk thread to the forkIO one, effectively 'freezing' the game for some time. Unfortunately this problem doesn't show up above, but I have experienced it on a larger game I'm currently programming using Prompt. - It is possible that the user clicks on the button between f1 and f2. Again, on this very simple example nothing seems to go wrong, but there shouldn't be anything between f1 and f2 as the GUI is on an inconsistent state. It should be noted that the scheduling problem can be mitigated using 'yield' on some key spots. This not only feels hackish, but also doesn't scale very well. Another approach that is sometimes adopted to solve this kind of problem is creating a main "sub-loop" with 'mainIteration'. This essentially removes the need for those nasty evil threads =).
subLoopAttempt :: AttemptCode subLoopAttempt showInfo entry button = do game <- guessGameNew attempts <- runPromptM subLoopMapping game showInfo $ "You took " ++ show attempts ++ " attempts." where subLoopMapping :: forall a. GuessP a -> IO a subLoopMapping (Print s) = showInfo s subLoopMapping Guess = do v <- newEmptyMVar cid <- onClicked button $ entryGetText entry >>= putMVar v guess <- subLoopGetMVar v signalDisconnect cid return (read guess)
Here comes the magic!
subLoopGetMVar :: MVar a -> IO a subLoopGetMVar v = do m <- tryTakeMVar v case m of Just r -> return r Nothing -> do quitting <- mainIteration when quitting (fail "quitting") subLoopGetMVar v
There are a couple of pitfalls in this approach as well: - The quitting code doesn't work very well anymore. Try to close the window before guessing right and you'll see an "user error" on the console. Some 'bracket' magic is needed to get out of the subloop without throwing errors at the user's face. - Every time we get into a subloop we add an overhead for every event the application receives. I don't know if this is important at all, maybe with lots of nested subloop. - The real problem is: what if the MVar gets full but does not generate an event? While 'subLoopGetMVar' waits for 'mainIteration', the game code should be executing already for a long time! Unfortunately I couldn't come up with a simple example that exposes the last problem listed above. But, for example, some network code could fill that MVar in a multiplayer internet game. In this case the game wouldn't proceed until an event was generated. It's known that to partially solve this problem it is possible to create a signal generator that runs every X milliseconds, giving an upper bound to the amount of time between putMVar being called and subLoopGetMVar finishing. This feels hackish and fragile as well, specially because it is difficult to hunt down bugs. But Prompt has a very *very* nice property we're missing to take advantage of here: it's is *pure*. In fact, I think that is one of the reasons why Ryan bothered sending us an e-mail -- you can not only plug different interfaces codes, but also plug no interface at all to make tests, with purity making matters very simple. Ryan also notes that "If you wanted to add undo, all you have to do is save off the current Prompt in the middle of runPromptM; you can return to the old state at any time." Eventually this feature rang some bells: you can save not only when you want to undo, but also when you want to ask something to the user. Unfortunately, I still haven't come up with a nice higher order function that generalizes this work without reinventing Prompt on an isomorphic type. Enough said, let's see how:
lastAttempt :: AttemptCode lastAttempt showInfo entry button = do game <- guessGameNew runPromptM' game where -- Signature required runPromptM' :: Prompt GuessP Int -> IO () -- note: not (IO Int)! runPromptM' (Prompt (Print s) c) = showInfo s >> runPromptM' (c ()) runPromptM' (Prompt Guess c) = do mfix $ \cid -> do let cont guess = do {signalDisconnect cid; runPromptM' (c $ read guess)} onClicked button $ entryGetText entry >>= cont return () runPromptM' (PromptDone attempts) = do showInfo $ "You took " ++ show attempts ++ " attempts."
After so many attempts looking with some much similar code, it may be hard to see exactly how our last attempt work. No threads, no MVars, no nothing. So I took out features, and now everything is better? =) Basically, we first assume that every time 'runPromptM'' is called, we're on Gtk's thread (which is easy in this case since there are no threads at all). Next, we see if we need to *wait* for something. In the Print case, we just call 'showInfo', so the code is the same as expanding 'subLoopMapping (Print s)' inside 'runPromptM'. This means that the Gtk event that called 'runPromptM'' will continue to execute the the next call to 'runPromptM'' as well. This is very nice, since it introduces no delays to the user (imagine a non-blocking showInfo -- e.g. printing on a textview). The PromptDone case is also very similar to what has been done before. However, in the Guess case we connect a signal to the button and return! This is where things get very different from the other approaches. When using 'forkIO', the forked thread would run from the game start until its end. When using 'mainIteration', the event that called 'subLoopAttempt' (in our case, the timeout) would execute until the end of the game. Instead, 'lastAttempt' will run only until the first Guess. Okay, so how do we proceed from here? The continuation of the 'Prompt' constructor goes inside 'cont's closure. When the user clicks on the button, it disconnects the signal and calls 'runPromptM'' again. Everything happens sequentially as I'm saying because there aren't any other threads playing with our continuation, so this not only removes the need for MVars but also fixes the whole problem of "will this run in the middle of that?". Even if the user could click twice at the same time, the Gtk main loop would execute only one event callback "concurrently" and by the time the other event gets its chance to execute we'll have disconnected its signal handler already. It's true that *another* callback would be connected if the guess was not right, but that doesn't cause any inconsistencies at all. Note also that we could have, for example, two buttons sharing the same continuation if their callbacks disconnected both 'ConnectID's before going on. No freezes, no races, no exceptions, no overheads. No generic 'runPromptM' abstraction as well, but I think the price is worth paying, specially because the other approaches have nasty subtle bugs. And we continue to have the possibility of using 'runPromptM' in our tests, for example. -- Oh, well. This e-mail got longer than I initially imagined, thanks God I started typing it on emacs already =). I'm looking forward suggestions on improvements and critics about problems in this last approach. Unfortunately the game I'm developing is still in an early stage, but I promise to release it under the GPL sometime soon =). Also, I welcome any meaningful comparison between 'lastAttempt' and 'callCC'. Thanks for reading until here, -- Felipe.

On Sun, 2008-01-13 at 14:53 -0200, Felipe Lessa wrote:
Problem solved? Not really:
- This kind of implementation hides lots of subtle bugs. For example, because of postGUIAsync being used in Print case, the user will see multiple dialog boxes at once and -- strangely enough -- he'll see first the last message printed. It isn't always easy to see this kind of bug at first sight, and it can be very hard to track it down.
You could use another thread :-) That is have an output thread that reads a queue from your game engine and only looks for the next output message at appropriate points.
- Another problem may happen with scheduling. For some reason, there are times in which it takes some time for the control to pass from the Gtk thread to the forkIO one, effectively 'freezing' the game for some time. Unfortunately this problem doesn't show up above, but I have experienced it on a larger game I'm currently programming using Prompt.
Are you linking using -threaded or not? If not then you need another trick to use cooperative scheduling between Gtk and the RTS.
- It is possible that the user clicks on the button between f1 and f2. Again, on this very simple example nothing seems to go wrong, but there shouldn't be anything between f1 and f2 as the GUI is on an inconsistent state.
It should be noted that the scheduling problem can be mitigated using 'yield' on some key spots. This not only feels hackish, but also doesn't scale very well.
You must not be using -threaded then I'm guessing. That'd solve the problem.
Another approach that is sometimes adopted to solve this kind of problem is creating a main "sub-loop" with 'mainIteration'. This essentially removes the need for those nasty evil threads =).
That's pretty ugly. I'd avoid that if I were you. Here's my suggestion: use two threads. One thread for the game logic and one thread for communicating with the user interface. Then use an input an output channel to post interesting events between the two. The GUI would then also post interesting events into the incoming channel for the view/ui thread. Of course you'd have to link using -threaded and use postGUISync/Async as appropriate from the view/ui thread. By serialising all button events into a channel it allows you to ignore button presses that happen at certain moments. And as I suggested above, it allows you to serialise the output events so you don't end up showing several dialogues to the user at once. Duncan

On Jan 13, 2008 4:01 PM, Duncan Coutts
On Sun, 2008-01-13 at 14:53 -0200, Felipe Lessa wrote: You could use another thread :-)
LOL, at first I thought of mail threads =).
That is have an output thread that reads a queue from your game engine and only looks for the next output message at appropriate points.
I'll comment on this shortly.
Are you linking using -threaded or not? If not then you need another trick to use cooperative scheduling between Gtk and the RTS. [snip] You must not be using -threaded then I'm guessing. That'd solve the problem.
Actually I tried with all combinations of -threaded/not -threaded and forkIO/forkOS. I'm using an uniprocessor, but a simple turn-based game shouldn't depend on dual-cores anyway =). Yes, those freezes do seem rather strange, and when I introduced some (unsafePerformIO . putStrLn) with the wall time they magically disappeared. I didn't try to pursue those little insects further because I got the feeling that no mather what, they would come back.
[...] using 'mainIteraction' [...] That's pretty ugly. I'd avoid that if I were you.
Yes. =)
Here's my suggestion: use two threads. One thread for the game logic and one thread for communicating with the user interface. Then use an input an output channel to post interesting events between the two. The GUI would then also post interesting events into the incoming channel for the view/ui thread.
Of course you'd have to link using -threaded and use postGUISync/Async as appropriate from the view/ui thread.
By serialising all button events into a channel it allows you to ignore button presses that happen at certain moments. And as I suggested above, it allows you to serialise the output events so you don't end up showing several dialogues to the user at once.
It seems to be a nice idea. I worry about intermediate states that shouldn't be observable (in my game the inputs the user is allowed to give change over the time -- it's a board game, so which pieces can move vary according to the current board), but what concerns me more after that bad experience with only one forked thread are the delays between the user giving an input (e.g. moving a piece) and the feedback being given (an animation of the result). The chain would be something like input given --> processed --> new board created --> shown (1) (2) (3) (4) So the interaction between the threads would be gtk: (1) ===\ /===> (4) channel: \===\ /===/ runPromptM: \===> (2) ===> (3) ===/ I'll try to code that ASAP and see how everything works together. If I do observe the same delay problem, I'll try to at least reproduce it on another machine and maybe create a simple test case. Other than that, I'm surprised you didn't comment about the last solution, as that's where I'm currently heading. =) Thanks for the reply, -- Felipe.

On Sun, 2008-01-13 at 16:37 -0200, Felipe Lessa wrote:
On Jan 13, 2008 4:01 PM, Duncan Coutts
wrote: On Sun, 2008-01-13 at 14:53 -0200, Felipe Lessa wrote:
Are you linking using -threaded or not? If not then you need another trick to use cooperative scheduling between Gtk and the RTS. [snip] You must not be using -threaded then I'm guessing. That'd solve the problem.
Actually I tried with all combinations of -threaded/not -threaded and forkIO/forkOS.
Use forkIO not forkOS.
I'm using an uniprocessor, but a simple turn-based game shouldn't depend on dual-cores anyway =). Yes, those freezes do seem rather strange, and when I introduced some (unsafePerformIO . putStrLn) with the wall time they magically disappeared.
Weirder.
I didn't try to pursue those little insects further because I got the feeling that no mather what, they would come back.
Is this unix or windows btw?
[...] using 'mainIteraction' [...] That's pretty ugly. I'd avoid that if I were you.
Yes. =)
Here's my suggestion: use two threads. One thread for the game logic and one thread for communicating with the user interface. [..] It seems to be a nice idea. I worry about intermediate states that shouldn't be observable (in my game the inputs the user is allowed to give change over the time -- it's a board game, so which pieces can move vary according to the current board), but what concerns me more after that bad experience with only one forked thread are the delays between the user giving an input ( e.g. moving a piece) and the feedback being given (an animation of the result). The chain would be something like
input given --> processed --> new board created --> shown (1) (2) (3) (4)
So the interaction between the threads would be
gtk: (1) ===\ /===> (4) channel: \===\ /===/ runPromptM: \===> (2) ===> (3) ===/
That should be fine. Haskell thread are quite sufficiently fast. The delays you're seeing are not because of general thread implementation slowness.
I'll try to code that ASAP and see how everything works together. If I do observe the same delay problem, I'll try to at least reproduce it on another machine and maybe create a simple test case.
Good plan. If you're using -threaded make sure you really only ever call gui methods from event callbacks or within postGUISync/Async or things will go wrong in various random ways. In fact it might be a better idea to use the cooperative scheduling trick and make sure it works with the single threaded rts.
Other than that, I'm surprised you didn't comment about the last solution, as that's where I'm currently heading. =)
Oh sorry, I didn't get that far :-) It looks like it works a lot nicer so go with it :-). Remember, in general it is possible to switch between the console IO style where you're in control and the GUI event inversion of control style system. It's the thread/event duality thing. Duncan

Felipe Lessa wrote: (abridged)
Ryan Ingram enlightened us with MonadPrompt as a very nice abstraction for turn-based games, allowing easy programming and testing.
I wonder how nicely it fits on a Gtk2Hs application. =)
The problem lies in the fact that Gtk is event-driven, so every time we ask the user for something, we have to wait for the corresponding event that will bring us his answer.
The standard way of solving the problem of running two sequential things at once is using threads [...]This not only feels hackish, but also doesn't scale very well. [...]This feels hackish and fragile as well, specially because it is difficult to hunt down bugs.
But Prompt has a very *very* nice property we're missing to take advantage of here: it's is *pure*.
"If you wanted to add undo, all you have to do is save off the current Prompt in the middle of runPromptM; you can return to the old state at any time."
Eventually this feature rang some bells: you can save not only when you want to undo, but also when you want to ask something to the user.
let's see how:
lastAttempt :: AttemptCode lastAttempt showInfo entry button = do game <- guessGameNew runPromptM' game where -- Signature required runPromptM' :: Prompt GuessP Int -> IO () -- note: not (IO Int)! runPromptM' (Prompt (Print s) c) = showInfo s >> runPromptM' (c ()) runPromptM' (Prompt Guess c) = do mfix $ \cid -> do let cont guess = do {signalDisconnect cid; runPromptM' (c $ read guess)} onClicked button $ entryGetText entry >>= cont return () runPromptM' (PromptDone attempts) = do showInfo $ "You took " ++ show attempts ++ " attempts."
No threads, no MVars, no nothing. No freezes, no races, no exceptions, no overheads.
Marvelous work! Here's a short summary: The general idea was to implement a game in a modular way, namely such that the game and interaction logic is written in a separate monad which can be "plugged" into different interfaces like command line, undo, GUI etc. . MonadPrompt (aka the free monad) lets you do exactly that. Command line is straightforward, Ryan showed how to do undo and Felipe's post shows how to do it in a GUI framework which are notorious for being event-based and thus a tricky target for this particular task. The insight is that the actions from the MonadPrompt like Prompt Guess c or Prompt (Print s) c *are* the game state. What to do in the state Prompt Guess c -- some function c ? Well, we wait for the user to press a button, and then we feed the text he entered in some text field to c which advances the game to a new state. More precisely, we register a button event for that and return control to the GUI framework for the waiting. What to do with a monadic value Prompt (Print s) c ? Well, we print the message and immediately proceed with c , i.e. without waiting for user input this time. In the end, the only unusual thing about our game state is that it already know how to continue, namely via the continuation c . Felipe explored another option, namely to run the game monad in a thread that communicates with a separate GUI thread. Conceptually, this is closer to the feeling of the game monad, namely that it "runs through". But getting the communication between threads right is a nightmare. And in a sense, /threads are exactly the abstraction we wanted to implement in the first place/, only with more problems. How are threads themselves implemented? Well, in essence, the scheduler which runs threads just sees states like Prompt ReadMVar c -- this thread waits for a message Prompt (PutMVar x) c -- dispatch a message and proceed and evolves them. Of course, ghc's threads are closer to the machine and hence more fine-grained than that (pure computations can be suspended) with corresponding advantages (more interleaving, good for staying responsive while doing work) and drawbacks (loss of atomicity). The reader may want to try to implement his own (toy-) thread library with Prompt . Solution here: K. Claessen. Poor man's concurrency monad. http://www.cs.chalmers.se/~koen/pubs/jfp99-monad.ps For less "toy", see also P. Li, S. Zdancewic. Combining events and threads for scalable network services. http://www.seas.upenn.edu/~lipeng/homepage/papers/lz07pldi.pdf Maybe the property that distinguishes the harmless game monad from the dreaded threads is: they have forks. :) I mean, threads run in parallel and can/need to communicate and spawn whereas the game monad runs as one and is unable to soliloquize.
Eventually this feature rang some bells: you can save not only when you want to undo, but also when you want to ask something to the user. Unfortunately, I still haven't come up with a nice higher order function that generalizes this work without reinventing Prompt on an isomorphic type.
Oh, what kind of generalization do you have in mind? Regards, apfelmus

On Jan 13, 2008 6:49 PM, apfelmus
K. Claessen. Poor man's concurrency monad. http://www.cs.chalmers.se/~koen/pubs/jfp99-monad.ps
P. Li, S. Zdancewic. Combining events and threads for scalable network services. http://www.seas.upenn.edu/~lipeng/homepage/papers/lz07pldi.pdf
Two great papers! Thanks for pointing them out!
Eventually this feature rang some bells: you can save not only when you want to undo, but also when you want to ask something to the user. Unfortunately, I still haven't come up with a nice higher order function that generalizes this work without reinventing Prompt on an isomorphic type.
Oh, what kind of generalization do you have in mind?
Leaking Prompt(..) in the export list to the GUI code seems wrong to me, I like 'runPromptM' because it hides the Prompt(..) data type from the user [module]. But after some rest I think I found a nice corresponding function:
contPromptM :: Monad m => (r -> m ()) -> (forall a. p a -> (a -> m ()) -> m ()) -> Prompt p r -> m () contPromptM done _ (PromptDone r) = done r contPromptM done cont (Prompt p c) = cont p (contPromptM done cont . c)
This way all the Prompts get hidden so that 'lastAttempt' may be coded as
lastAttempt' :: AttemptCode lastAttempt' showInfo entry button = guessGameNew >>= contPromptM done cont where cont :: forall a. GuessP a -> (a -> IO ()) -> IO () -- signature needed cont (Print s) c = showInfo s >> c () cont Guess c = do mfix $ \cid -> onClicked button $ do {signalDisconnect cid; guess <- entryGetText entry; c (read guess)} return () done attempts = showInfo $ "You took " ++ show attempts ++ " attempts."
Nice and clean, and much better to read as well. Now the only question unanswered for me is if there are any relations between (forall a. p a -> (a -> m ()) -> m ()) -- from contPromptM and (ContT r m a -> (a -> m r) -> m r) -- from runContT besides the fact that both carry a continuation. I have a feeling that I am missing something clever here. Cheers, -- Felipe.

Felipe Lessa wrote:
apfelmus wrote:
Oh, what kind of generalization do you have in mind?
Leaking Prompt(..) in the export list to the GUI code seems wrong to me, I like 'runPromptM' because it hides the Prompt(..) data type from the user [module]. But after some rest I think I found a nice corresponding function:
contPromptM :: Monad m => (r -> m ()) -> (forall a. p a -> (a -> m ()) -> m ()) -> Prompt p r -> m () contPromptM done _ (PromptDone r) = done r contPromptM done cont (Prompt p c) = cont p (contPromptM done cont . c)
This way all the Prompts get hidden so that 'lastAttempt' may be coded as
lastAttempt' :: AttemptCode lastAttempt' showInfo entry button = guessGameNew >>= contPromptM done cont where cont :: forall a. GuessP a -> (a -> IO ()) -> IO () -- signature needed cont (Print s) c = showInfo s >> c () cont Guess c = do mfix $ \cid -> onClicked button $ do {signalDisconnect cid; guess <- entryGetText entry; c (read guess)} return () done attempts = showInfo $ "You took " ++ show attempts ++ " attempts."
Nice and clean, and much better to read as well.
The type of contPromptM is even more general than that: casePromptOf' :: (r -> f b) -> (forall a,b. p a -> (a -> f b) -> f b) -> Prompt p r -> f b casePromptOf' done cont (PromptDone r) = done r casePromptOf' done cont (Prompt p c ) = cont p (casePromptOf' done cont . c) In other words, it's (almost) the case expression / dual for the Prompt data type. So, only exporting this function and not the Prompt constructors is like exporting only either :: (a -> c) -> (b -> c) -> Either a b -> c instead of Left and Right for pattern matching. This way, you can do (simulated) pattern matching with them, but may not use them for construction. Which is probably what you want here. Except that there is a subtle difference, namely that c in Prompt p c has type c :: a -> Prompt p r whereas the argument to casePromptOf' expects it as c' = casePromptOf' done cont . c :: a -> f b This means that not exporting constructors could reduce the number of programs that are possible to implement, but I can't (dis-)prove it. (That's basically the question at the end of http://thread.gmane.org/gmane.comp.lang.haskell.cafe/31842/focus=32218). Of course, you can just change the argument type to (forall a,b. p a -> (a -> Prompt p b) -> f b) for the full flexibility.
Now the only question unanswered for me is if there are any relations between
(forall a. p a -> (a -> m ()) -> m ()) -- from contPromptM
and
(ContT r m a -> (a -> m r) -> m r) -- from runContT
besides the fact that both carry a continuation. I have a feeling that I am missing something clever here.
The link to ContT m a = (forall b . (a -> m b) -> m b) is apparent in the case of casePromptOf' and is no surprise: you can omit p a and Prompt p r entirely and implement them directly as continuations (thereby loosing the ability to use it with different m, which would defeat the whole point here.) See also Implementing the State Monad. http://article.gmane.org/gmane.comp.lang.haskell.cafe/31486 for the details. Regards, apfelmus

On Jan 14, 2008 8:27 PM, apfelmus
The type of contPromptM is even more general than that:
casePromptOf' :: (r -> f b) -> (forall a,b. p a -> (a -> f b) -> f b) -> Prompt p r -> f b casePromptOf' done cont (PromptDone r) = done r casePromptOf' done cont (Prompt p c ) = cont p (casePromptOf' done cont . c)
(I guess the forall b inside 'cont' is a typo?) Actually, it can be as general as casePromptOf :: (r -> b) -> (forall a. p a -> (a -> b) -> b) -> Prompt p r -> b casePromptOf done cont (PromptDone r) = done r casePromptOf done cont (Prompt p c ) = cont p (casePromptOf done cont . c) =) And, just for the record, runPromptAgain :: Monad m => (forall a. p a -> m a) -> Prompt p r -> m r runPromptAgain f = casePromptOf return ((>>=) . f)
The link to ContT m a = (forall b . (a -> m b) -> m b) is apparent in the case of casePromptOf' and is no surprise: you can omit p a and Prompt p r entirely and implement them directly as continuations (thereby loosing the ability to use it with different m, which would defeat the whole point here.) See also
Implementing the State Monad. http://article.gmane.org/gmane.comp.lang.haskell.cafe/31486
for the details.
I've read that e-mail when it was sent but didn't understand it fully. I guess now I'm in a better condition, but I still have a lot to learn about these little warm, fuzzy things. Actually, the more I see, the less I understand why some people are afraid of them... it must really be the name 'monad'. Thanks for all the help guys! Next I'll try to reproduce the freezes I was getting with my first forkIO approach. Cheers, -- Felipe.

Felipe Lessa wrote:
apfelmus wrote:
The type of contPromptM is even more general than that:
casePromptOf' :: (r -> f b) -> (forall a,b. p a -> (a -> f b) -> f b) -> Prompt p r -> f b casePromptOf' done cont (PromptDone r) = done r casePromptOf' done cont (Prompt p c ) = cont p (casePromptOf' done cont . c)
(I guess the forall b inside 'cont' is a typo?)
No, it's intentional and not less general than
casePromptOf :: (r -> b) -> (forall a. p a -> (a -> b) -> b) -> Prompt p r -> b casePromptOf done cont (PromptDone r) = done r casePromptOf done cont (Prompt p c ) = cont p (casePromptOf done cont . c)
since we can use data Const c b = Const { unConst :: c } and set f = (Const b) yielding casePromptOf :: forall p,c. (r -> c) -> (forall a. p a -> (a -> c) -> c) -> Prompt p r -> c casePromptOf return bind = unConst . casePromptOf' (Const . return) bind' where bind' :: forall a,b. p a -> (a -> Const c b) -> Const c b bind' p c = Const $ bind p (unConst . c) In other words, casePromptOf can be defined with casePromptOf' and a clever choice of f .
And, just for the record,
runPromptAgain :: Monad m => (forall a. p a -> m a) -> Prompt p r -> m r runPromptAgain f = casePromptOf return ((>>=) . f)
I thought that casePromptOf would not be general enough to write this very definition runPromptAgain' f = casePromptOf' return ((>>=) . f) that's why I used a type constructor f b instead, with f = m the monad in mind. The difference is basically that the (>>=) in runPromptAgain' is expected to be polymorphic (>>=) :: forall b. m a -> (a -> m b) -> m b whereas the (>>=) in runPromptAgain is specialized to the final type m r of runPromptAgain , i.e. (>>=) :: m a -> (a -> m r) -> m r Unfortunately, I failed to realize that casePromptOf is in turn not less general than casePromptOf' rendering my approach pretty useless :) I mean, if the second argument in casePromptOf' :: (r -> f c) -> (forall a,b. p a -> (a -> f b) -> f b) -> Prompt p r -> f c is polymorphic, we can certainly plug it into casePromptOf :: (r -> f c) -> (forall a. p a -> (a -> f c) -> f c) -> Prompt p r -> f c and thus define casePromptOf' in terms of casePromptOf : casePromptOf' return bind = casePromptOf return bind The above equivalence of a type constructor f and a simple type c in certain cases applies to the continuation monad, too. I mean that ContT r m a is equivalent to Cont (m r) a and even ContT' m a is equivalent to forall r. Cont (m r) a for the more type safe version data ContT' m a = ContT' (forall r. (a -> m r) -> m r) So, it's pretty clear that ContT isn't really a monad transformer since m doesn't need to be a monad at all. Put differently, the Control.Monad.Cont module needs some cleanup since type synonyms type ContT r m a = Cont (m r) a type ContT' m a = forall r. Cont (m r) a (or newtypes for type classery) are enough. Regards, apfelmus

apfelmus wrote:
Felipe Lessa wrote:
casePromptOf :: (r -> b) -> (forall a. p a -> (a -> b) -> b) -> Prompt p r -> b casePromptOf done cont (PromptDone r) = done r casePromptOf done cont (Prompt p c ) = cont p (casePromptOf done cont . c)
[is just as general as]
casePromptOf' :: (r -> f c) -> (forall a,b. p a -> (a -> f b) -> f b) -> Prompt p r -> f c
That's nice. So let's implement Prompt differently, using casePromptOf as a template:
newtype Prompt p r = Prompt { runP :: forall b . (r -> b) -> (forall a . p a -> (a -> b) -> b) -> b }
We can define a Monad instance easily enough:
instance Monad (Prompt p) where return a = Prompt $ \done _ -> done a f >>= g = Prompt $ \done prm -> runP f (\x -> runP (g x) done prm) prm
prompt can be implemented as follows:
instance MonadPrompt (Prompt p) where prompt p = \done prm -> prm p done
And finally define some handy functions for running it,
runPromptC :: (r -> b) -> (forall a . p a -> (a -> b) -> b) -> Prompt p r -> b runPromptC ret prm p = runP p ret prm
(runPromptC is just a different name for casePromptOf)
runPromptM :: Monad m => (forall a . p a -> m a) -> Prompt p r -> m r runPromptM prm = runPromptC return (\p cont -> prm p >>= cont)
The interesting point here is that by working with continuations, we could eliminate the recursive call of (>>=) in its own implementation, curing the quadratic slowdown for left associative uses of (>>=). enjoy, Bertram P.S. I've written a small peg solitaire game using Prompt and gtk2hs, available from http://int-e.home.tlink.de/haskell/solitaire.tar.gz Maybe it's interesting to somebody.

On Jan 14, 2008 2:28 PM, Felipe Lessa
lastAttempt' :: AttemptCode lastAttempt' showInfo entry button = guessGameNew >>= contPromptM done cont where cont :: forall a. GuessP a -> (a -> IO ()) -> IO () -- signature needed cont (Print s) c = showInfo s >> c () cont Guess c = do mfix $ \cid -> onClicked button $ do {signalDisconnect cid; guess <- entryGetText entry; c (read guess)} return () done attempts = showInfo $ "You took " ++ show attempts ++ " attempts."
Excellent work; I love it. I'll definitely have to give this a try when I get back from vacation. I'd been wondering what the best way to interface with GUI code is and it's nice to have a sample to work from. -- ryan
participants (5)
-
apfelmus
-
Bertram Felgenhauer
-
Duncan Coutts
-
Felipe Lessa
-
Ryan Ingram