Re: [Haskell-cafe] implementing try for RWST ?

2007-04-17 Thread Chris Kuklewicz
Brandon S. Allbery KF8NH wrote:
 
 On Apr 17, 2007, at 0:03 , [EMAIL PROTECTED] wrote:
 eventually run in the IO monad. One may wonder then why do we need
 RWST transformer, given that the IO monad can implement both the state
 
 For what it's worth, I got the impression that RWST was an example of a
 complex monad transformer --- not necessarily something useful.
 

I actually used RWS (not RWST in this case).  The analysis and transformation of
the regular expression parse tree in regex-tdfa is done by execRWS with monad 
type:

 type PM = RWS (Maybe GroupIndex) [Either Tag GroupInfo] ([OP]-[OP],Tag)

And to make it more complicated, some of the operations are via GHC's recursive
'mdo' syntax.  The reader is tracking which capture group we are inside (if any)
and the writer collects two streams of included Tags and capture GroupInfo.  The
state is a difference list of all the OP's and the next available Tag.

I use all of 'tell' 'listens' 'ask' 'local' 'get' 'put'

-- 
Chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] implementing try for RWST ?

2007-04-16 Thread tpledger
Jeremy Shaw wrote:
 :
 | However, I think this is buggy, because changes
 | to 's' and 'w' will be lost if 'm' raises an
 | exception.
 :


That's determined by the way you stack your monad
transformers when declaring the type: adding error handling
to a writer monad, or adding writing to an error handling
monad.  For a concrete example, see the result types in the
following.  The first has the Either inside the tuple, and
the second has the tuple inside the Either.

Prelude :t Control.Monad.Writer.runWriter .
Control.Monad.Error.runErrorT
Control.Monad.Writer.runWriter .
Control.Monad.Error.runErrorT :: Control.Monad.Error.ErrorT
e (Control.Monad.Writer.Writer w) a
- (Either e a, w)
Prelude :t either Left Right .
Control.Monad.Writer.runWriterT
either Left Right . Control.Monad.Writer.runWriterT ::
Control.Monad.Writer.WriterT w (Either a) a1 - Either a
(a1, w)


Regards,
Tom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] implementing try for RWST ?

2007-04-16 Thread oleg

The examples presented so far seem to show that the computation will
eventually run in the IO monad. One may wonder then why do we need
RWST transformer, given that the IO monad can implement both the state
and writer. At the very least me need the reader transformer, which is
the least demanding monad. We can do away with the reader as well,
depending on the circumstances (e.g., one may use implicit
parameters or implicit configurations, or just pass IORefs). 

The pure IO or ReaderIO solution has, besides simplicity, the
advantage of being more expressive. Monad transformers, besides
inefficiency, impose the rigid layering of effects, and so cannot
express some useful computations. The drawbacks of monad transformers
and their limited expressivity are not often discussed, unfortunately.

The following code shows Jeremy Shaw's example, with both persistent
and backed out state. The combinator tryC handles the exception and
preserves the state accumulated at the point of exception. In
contrast, tryBC undoes the changes to the state in case of
exception. Both combinators have their uses.

module T where

import Control.Monad.Reader
import Data.IORef
import Control.Exception
import Prelude hiding (catch)

type ReaderIO a v = ReaderT a IO v
type StateIO a v = ReaderIO (IORef a) v

type Counter = Integer

-- |Increment the counter by 1
incIO :: StateIO Counter ()
incIO = do
cref - ask
c - liftIO $ readIORef cref
let c' = c + 1
liftIO $ writeIORef cref c'
liftIO $ putStrLn (Incrementing counter to:  ++ show c')

-- get the current value of the counter
getC :: StateIO Counter Counter
getC = ask = liftIO . readIORef

-- Try that preserves the state
tryC :: ReaderIO a v - (Exception - ReaderIO a v) - ReaderIO a v
tryC action onerr = do
r - ask
liftIO $ catch (runReaderT action r) (\e - runReaderT (onerr e) r)

-- Try that backs up the state
tryBC :: StateIO a v - (Exception - StateIO a v) - StateIO a v
tryBC action onerr = do
r - ask
oldstate - liftIO $ readIORef r
liftIO $ catch (runReaderT action r) 
   (\e - do
  writeIORef r oldstate
  runReaderT (onerr e) r)

-- The run function
runC :: Counter - StateIO Counter v - IO v
runC v a = newIORef v = runReaderT a

test = runC 0 (do
incIO
v - tryC (die  (return $ Right ok)) (return . Left . show)
c - getC -- get the resulting counter
liftIO $ print (v,c))
 where
  -- |increment the counter by one and then die
  die = incIO  error die!

{-
*T test
Incrementing counter to: 1
Incrementing counter to: 2
(Left die!,2)
-}


-- the same but with backtrackable state
test2 = runC 0 (do
incIO
v - tryBC (die  (return $ Right ok)) (return . Left . show)
c - getC
liftIO $ print (v,c))
 where
  -- |increment the counter by one and then die
  die = incIO  error die!

{-
*T test2
Incrementing counter to: 1
Incrementing counter to: 2
(Left die!,1)
-}

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] implementing try for RWST ?

2007-04-16 Thread Brandon S. Allbery KF8NH


On Apr 17, 2007, at 0:03 , [EMAIL PROTECTED] wrote:

eventually run in the IO monad. One may wonder then why do we need
RWST transformer, given that the IO monad can implement both the state


For what it's worth, I got the impression that RWST was an example of  
a complex monad transformer --- not necessarily something useful.


--
brandon s. allbery  [solaris,freebsd,perl,pugs,haskell]   
[EMAIL PROTECTED]
system administrator  [openafs,heimdal,too many hats]   
[EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon university   
KF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] implementing try for RWST ?

2007-04-13 Thread Jeremy Shaw
Hello,

I defined a newtype like this (the ()s will be replace with
something more useful in the future):

 newtype DryRunIO a = DryRunIO { runDryRunIO :: RWST Bool () () IO a }
deriving (Monad, MonadIO, MonadError IOError, MonadFix, Functor, 
 MonadReader Bool, MonadWriter (), MonadState ())

 run :: Bool - DryRunIO a - IO a
 run dryRun action = (runRWST (runDryRunIO action)) dryRun () = \ (a, _, _) 
 - return a

and I want to define a function similar to |try| like this:

 tryDR :: DryRunIO a - DryRunIO (Either IOError a)
 tryDR m = catchError (m = return . Right) (return . Left)

unfortunately, when I use it, it does not work the way I want:

*Main run False (tryDR (error cheese))
*** Exception: cheese

This is because 'error' raises an |Exception|, not a |IOError|.

I would like to instead define tryDR to deal with exceptions:

 newtype DryRunIO a = DryRunIO { runDryRunIO :: RWST Bool () () IO a }
deriving (Monad, MonadIO, MonadError Exception, MonadFix, Functor, 
 MonadReader Bool, MonadWriter (), MonadState ())

 tryDR :: DryRunIO a - DryRunIO (Either Exception a)
 tryDR m = catchError (m = return . Right) (return . Left)

But to do this, I need an different instance of MonadError for IO,
namely:

 instance MonadError Exception IO where
   throwError = throwIO
   catchError = catch -- (from Control.Exception)

However, if I add that to my module I get this error:

Functional dependencies conflict between instance declarations:
  instance MonadError Exception IO -- Defined at /tmp/DR.hs:17:0
  instance MonadError IOError IO -- Defined in Control.Monad.Error

Where do I go from here? Also, what is the justificiation for the
current default of IOError instead of the more general Exception? 

thanks!
j.

ps. As a hack I have implemented tryDR as:

 tryDR' :: DryRunIO a - DryRunIO (Either Exception a)
 tryDR' (DryRunIO m) = DryRunIO $ RWST $ \r s - 
catch (runRWST m r s = \(a, s, w) - return (Right a, s, w))  -- 
 uses catch from Control.Exception
  (\e - runRWST (return $ Left e) r s)

However, I think this is buggy, because changes to 's' and 'w' will be
lost if 'm' raises an exception. For example in:

 tryDR' (io $ putStr hello  updatePosition (length hello)  error 
 goodbye)

The updatedPosition would reflect the position before the tryDR, but
the cursor on the screen would be somewhere else. It is my hope that
the earlier definition does not have this bug.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe