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

2008-01-18 Thread Bertram Felgenhauer
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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-01-15 Thread Felipe Lessa
On Jan 14, 2008 8:27 PM, apfelmus [EMAIL PROTECTED] 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?)

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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-01-14 Thread Felipe Lessa
On Jan 13, 2008 6:49 PM, apfelmus [EMAIL PROTECTED] 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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2008-01-14 Thread Ryan Ingram
On Jan 14, 2008 2:28 PM, Felipe Lessa [EMAIL PROTECTED] wrote:
  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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe