Re: a breaking monad

2003-08-01 Thread Tomasz Zielonka
On Thu, Jul 31, 2003 at 05:15:33PM -0400, Derek Elkins wrote:
 On Thu, 31 Jul 2003 13:18:40 -0700
 Hal Daume [EMAIL PROTECTED] wrote:
 
  so, my questions are: does this exist in some other form I'm not aware
  of?  is there something fundamentally broken about this (sorry for the
  pun)?  any other comments, suggestions?
 
 This looks like a bizarre rendition of the Error/Exception monad.
 
 I believe the function breakable would be fairly accurately
 represented with '\b - runErrorT b = either return return' and use
 throwError for break.

I used the Cont(inuation) monad for similar purposes. This has an
advantage that you can choose a place to break (jump?) into, each place
having a possibly different type of return value.

Here's an example:

  module A where

  import Control.Monad.Cont
  import Control.Monad

  fun :: IO ()
  fun = (`runContT` return) $ do
  r - callCC $ \exit - do
  r1 - callCC $ \exit1 - do
  r2 - callCC $ \exit2 - do
  r3 - callCC $ \exit3 - do
  x - liftIO (readLn :: IO Int)
  when (x == 2) (exit2 two)   -- jump with a String
  when (x == 1) (exit1 1)   -- jump with an Int
  when (x == 3) (exit3 [three])   -- with [String]
  (exit other)
  return []
  liftIO $ putStrLn $ r3:  ++ show r3
  exit1 3   -- jump with Int
  return three
  liftIO $ putStrLn $ r2:  ++ show r2
  return 2
  liftIO $ putStrLn $ r1:  ++ show r1
  return (show r1)
  liftIO $ putStrLn $ r:  ++ show r

After running fun, type a number ([1..4]) and press Enter.

PS. Are there other uses of Cont monad?

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: a breaking monad

2003-08-01 Thread Derek Elkins
On Fri, 1 Aug 2003 12:02:00 +0200
Tomasz Zielonka [EMAIL PROTECTED] wrote:

 On Thu, Jul 31, 2003 at 05:15:33PM -0400, Derek Elkins wrote:
  On Thu, 31 Jul 2003 13:18:40 -0700
  Hal Daume [EMAIL PROTECTED] wrote:
  
   so, my questions are: does this exist in some other form I'm not
   aware of?  is there something fundamentally broken about this
   (sorry for the pun)?  any other comments, suggestions?
  
  This looks like a bizarre rendition of the Error/Exception monad.
  
  I believe the function breakable would be fairly accurately
  represented with '\b - runErrorT b = either return return' and
  use throwError for break.
 
 I used the Cont(inuation) monad for similar purposes. This has an
 advantage that you can choose a place to break (jump?) into, each
 place having a possibly different type of return value.

I was thinking of providing a Cont example too.

 PS. Are there other uses of Cont monad?

I've used it for resumptions, and I imagine you could use it to handle
the CP in an optimized via CPS function, though that likely isn't
worthwhile (heh).  Hinze's Backtracking monad uses CPS but not the Cont
monad, though it may be representable with ContT over Cont, I'm pretty
sure shift/reset can get the same effect.

Less immediately practical, I've experimented with shift/reset with it.
I'm kind of interested in translating Filinsky's monadic reification and
reflection into Haskell with the Cont(T) monad.  This would probably
have no real practical benefit (or would it... run-time changing?), I
believe a similar effect usage-wise can be achieved by using a class for
the monad parameter (MonadState/etc.) It would be more practical if a
compiler internally supported a Cont(T) monad.

Anyways, most of my uses of the Cont monad have been for my own personal
entertainment, and usually I break the abstraction (using
Control.Monad.Cont) to do the things I want.  I don't know if I've ever
written something that's used callCC that I kept.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: a breaking monad (to haskell cafe)

2003-08-01 Thread Iavor Diatchki
hi,

Derek Elkins wrote:
Anyways, most of my uses of the Cont monad have been for my own personal
entertainment, and usually I break the abstraction (using
Control.Monad.Cont) to do the things I want.  I don't know if I've ever
written something that's used callCC that I kept.
except for entertainment purposes i feel pretty much the same way :-)
i think that in probably 95% of the cases that arise there is a simpler 
monad that does the job (i.e. exceptions, backtracking, etc).  of course 
it could be that we are simply not used to program using the callcc.

bye
iavor


--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


a breaking monad

2003-07-31 Thread Hal Daume
i've noticed in a lot of my imperative-looking monadic code, i have lots
of stuff that looks like:

 ... = do
   q - some test
   if q
 then return some constant
 else do
   major code body here

lots of these things embedded makes the code hard to read and introduces
way too much indentation (i'm one of those who doesn't like curly
braces).

one solution to this is to write it as:

 ... = do
   q - some test
   if q then return some constant else do
   major code body here

but this is ugly, IMO :).

my solution was to fashion a monad transformer that supports a break
statement.  basically, it looks like:

 data Break b m a = Break { runBreak :: m (Maybe b, a) }
 
 instance MonadTrans (Break b) where
   lift x = Break $ do a - x; return (Nothing, a)
 
 instance Monad m = Monad (Break b m) where
   return a = Break $ return (Nothing, a)
   b = k  = Break $ runBreak b = \ (broken, a) -
   case broken of
 Nothing - runBreak (k a)
 Just br - return (Just br, undefined)
 
 breakable :: Monad m = Break a m a - m a
 breakable b = runBreak b = \ (broken, a) -
 case broken of
   Nothing - return a
   Just br - return br
 
 break :: Monad m = b - Break b m a
 break b = Break (return (Just b, undefined))

essentially you introduce code blocks with the breakable function and
then can break with the break function.  a useful combinator i've found
is:

 breaksTo :: Monad m = m Bool - b - Break b m ()
 breaksTo k b = lift k = \x - if x then break b else return ()

using this, you can write stuff which looks like:

 test1 :: IO [String]
 test1 = breakable $ do
   lift $ putStrLn Enter something, or nothing to quit:
   l - lift $ getLine
   when (null l) $ break []
   rest - lift test1
   return (l:rest)
 
 test2 :: IO ()
 test2 = breakable $ repeatM $ do 
   x - lift $ getLine = passThrough putStrLn
   when (null x) $ break ()
 
 test3 :: Handle - IO [String]
 test3 h = breakable $ do
   hIsEOF h `breaksTo` []
   lift $ do 
 l - hGetLine h
 rest - test3 h
 return (l:rest)

where passThrough and repeatM are:

 repeatM :: Monad m = m () - m ()
 repeatM x = x  repeatM x
 
 passThrough :: Monad m = (a - m b) - a - m a
 passThrough f a = f a  return a

so, my questions are: does this exist in some other form I'm not aware
of?  is there something fundamentally broken about this (sorry for the
pun)?  any other comments, suggestions?


--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: a breaking monad

2003-07-31 Thread Derek Elkins
On Thu, 31 Jul 2003 13:18:40 -0700
Hal Daume [EMAIL PROTECTED] wrote:

 so, my questions are: does this exist in some other form I'm not aware
 of?  is there something fundamentally broken about this (sorry for the
 pun)?  any other comments, suggestions?

This looks like a bizarre rendition of the Error/Exception monad.

I believe the function breakable would be fairly accurately
represented with '\b - runErrorT b = either return return' and use
throwError for break.

Also, your motivating example is ambiguous.  I think you mainly care
about the case where the test is testing for some exceptional
condition.  I personally wouldn't want to use this style every place I
would use an if.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: a breaking monad

2003-07-31 Thread Hal Daume
 This looks like a bizarre rendition of the Error/Exception monad.

Yes, of course.  *Hal slaps himself*

Thanks.

 Also, your motivating example is ambiguous.  I think you mainly care
 about the case where the test is testing for some exceptional
 condition.  I personally wouldn't want to use this style every place I
 would use an if.

Definitely not!  :)

 - Hal
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell