a breaking monad

Tomasz Zielonka t.zielonka@students.mimuw.edu.pl
Fri, 1 Aug 2003 12:02:00 +0200


On Thu, Jul 31, 2003 at 05:15:33PM -0400, Derek Elkins wrote:
> On Thu, 31 Jul 2003 13:18:40 -0700
> "Hal Daume" <t-hald@microsoft.com> 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