[Haskell-cafe] Are there standard idioms for lazy, pure error handling?

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Sun Dec 13 06:57:07 EST 2009


Duncan Coutts wrote:
> Another approach that some people have advocated as a general purpose
> solution is to use:
> 
> data Exceptional e a = Exceptional {
>   exception :: Maybe e
>   result    :: a
> }
> 
> However it's pretty clear from the structure of this type that it cannot
> cope with lazy error handling in sequences. If you try it you'll find
> you cannot do it without space leaks.

It's not all that clear. Consider this toy example (from a private
discussion with Henning Thielemann a while ago), which runs in
constant space:

    import System.IO.Unsafe
    import System.Environment
    import Control.Monad
    import Data.List

    data Exceptional e a =
        Exceptional { exception :: Maybe e, result :: a }

    ok      a = Exceptional Nothing  a
    fault e a = Exceptional (Just e) a

    faulty :: Int -> IO (Exceptional Int [Int])
    faulty 0 = return (fault 0 [])
    faulty 1 = return (ok [])
    faulty n = unsafeInterleaveIO $ do
        -- getChar
        r <- faulty (n-2)
        return $ Exceptional (exception r) (n : result r)

    main = do
        n <- readIO . head =<< getArgs
        Exceptional exc res <- faulty n
        print $ last res
        when (n `mod` 3 == 0) $ print exc

This works because ghc's garbage collector evaluates record selectors.
(There are a simpler cases where this matters, for example
    last $ fst $ unzip [(a,a) | a <- [1..100000000]]
which also runs in constant space.)

The approach is very fragile, though. For example, if we change main to

    main = do
        n <- readIO . head =<< getArgs
        f <- faulty n
        print $ last (result f)
        when (n `mod` 3 == 0) $ print (exception f)

then the space leak reoccurs - doing the pattern match on the
Excpeptional constructor before using the result is essential.

Bad things also happen if ghc's optimiser turns the record selectors
into explicit pattern matches in the worker ('faulty' in the example).

Kind regards,

Bertram


More information about the Haskell-Cafe mailing list