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

apfelmus apfelmus at quantentunnel.de
Mon Jan 14 17:27:19 EST 2008


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



More information about the Haskell-Cafe mailing list