[Haskell-cafe] Re: MonadPrompt + Gtk2Hs = ?

Felipe Lessa felipe.lessa at gmail.com
Mon Jan 14 15:28:39 EST 2008


On Jan 13, 2008 6:49 PM, apfelmus <apfelmus at quantentunnel.de> wrote:
>    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.


More information about the Haskell-Cafe mailing list