[Haskell-cafe] Avoiding lazy evaluation in an ErrorT computation

Don Stewart dons at galois.com
Mon Jul 7 18:50:35 EDT 2008


Just use 'rnf', from the Control.Parallel namespace.

ryani.spam:
> This is the classic "exception embedded in pure value" problem with
> lazy languages.  There's no need for the "a" returned by "return" to
> be evaluated.
> 
> Even using "seq" isn't quite good enough:
> 
> > boom2 = [1 `div` 0]
> 
> ghci> doTinIO (boom2 `seq` return boom2)
> Right [*** Exception: divide by zero
> 
> If you want to guarantee that all embedded exceptions have been
> excised from a pure value, you need something like deepSeq; see
> http://hackage.haskell.org/packages/archive/hxt/7.4/doc/html/Control-Strategies-DeepSeq.html
> 
>   -- ryan
> 
> On 7/7/08, Tim Bauer <bauertim at eecs.orst.edu> wrote:
> > The file below models a problem I have been trying to figure out.
> > This file simplifies my original code, while still illustrating
> > the problem.
> >
> > > import Prelude hiding (catch)
> > > import Control.Monad.Reader
> > > import Control.Monad.Error
> > > import Control.Exception
> > > import System.IO(readFile)
> > > import Data.Either(either)
> >
> >
> > Our monad transformer is an ErrorT which wraps the IO monad.
> > ErrorT allows us to use throwError, but we won't use it in this example.
> >
> > > type T a = ErrorT String IO a
> >
> > The following runs a (T a) in the context of the IO monad.
> > We wrap runErrorT in try so as to catch things like division
> > by zero and what not.
> >
> > > doTinIO :: T a -> IO (Either String a)
> > > doTinIO ta = do
> > >  exesa <- try (runErrorT ta) -- IO (Either Exception (Either String a))
> > >  return $ case exesa  of
> > >    Left  x   -> Left ("EX: "++(show x))
> > >    Right esa -> esa
> > >
> > > boom = 1 `div` 0
> > > b1 = return boom :: T Int
> > > bad = doTinIO b1
> >
> > The above, bad, results in:
> >   Right *** Exception: divide by zero
> > My hope was to get
> >   Left "EX: divide by zero"
> >
> > I cannot understand why the `try' does not get a chance at the
> > erroneous calculation. That is, I want the try to catch
> > the runtime exception.
> >
> > Indeed, if the IO computation is strictly computed, I  get
> > the proper result.
> >
> > > g1 = boom `seq` (return boom :: T Int)
> > > good = doTinIO g1
> >
> > Stuff that raises exceptions in IO actions does not work either.
> >
> > > g2 = doTinIO (return boom)
> >
> > Results in: ``Right *** Exception: divide by zero''
> > However, other actions that do raise errors work correctly.
> >
> > It appears the value of the computation must be used
> > as the next two examples show.
> >
> > > g3 = doTinIO (liftIO (readFile "nonexistent"))
> > > g4 = doTinIO (liftIO (print boom))
> >
> > My problem is that I control `doTinIO', but someone else provides
> > the computation (T a). I cannot force callers to strictly evaluate
> > their computations.
> >
> > I've tried three other variants (given below) that are all
> > nearly equivalent.
> >
> > > handler :: Exception -> IO (Either String a)
> > > handler = return . Left . ("EX: "++) . show
> > >
> > > doTinIO2 :: T a -> IO (Either String a)
> > > doTinIO2 ta = catch (runErrorT ta >>= evaluate) handler
> > >
> > > doTinIO3 :: T a -> IO (Either String a)
> > > doTinIO3 ta = do
> > >  esa <- catch (runErrorT ta) handler
> > >  case esa of
> > >    Right a -> catch (evaluate (return a)) handler
> > >    l -> return l
> > >
> > > doTinIO4 :: T a -> IO (Either String a)
> > > doTinIO4 ta = catch (runErrorT ta) handler
> >
> > *Main> doTinIO2 b1
> > Right *** Exception: divide by zero
> > *Main> doTinIO3 b1
> > Right *** Exception: divide by zero
> > *Main> doTinIO4 b1
> > Right *** Exception: divide by zero
> >
> > Any suggestions? Thanks all.
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list