[Haskell-cafe] How to use Control.Failure?
Michael Snoyman
michael at snoyman.com
Sat Dec 19 11:14:09 EST 2009
On Sat, Dec 19, 2009 at 4:46 PM, ntupel <ntupel at googlemail.com> wrote:
> I have looked at the recently released Control.Failure library but I
> admit, I couldn't understand it completely. So given the example
> below, how would Control.Failure help me here?
>
> Thanks,
> nt
>
>
> -- Theirs (other library code stubs)
> data TheirError = TheirErrorCase deriving Show
> data TheirData = TheirData deriving Show
>
> theirFunc :: [String] -> Either TheirError TheirData
> theirFunc = undefined
>
>
> -- Mine (my own code stubs)
> data MyError = MyErrorCase deriving Show
> data MyData = MyData deriving Show
>
> myFuncA :: TheirData -> Either MyError MyData
> myFuncA = undefined
>
>
> -- Ugly. How to apply Control.Failure here?
> myFuncB :: IO (Either MyError MyData)
> myFuncB = do
> let x = theirFunc []
> case x of
> Right x' -> return $ myFuncA x'
> Left _ -> return . Left $ MyErrorCase
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
Well, here's one way of doing it. You have lots of choices here; these are
the decisions I made in implementing the code:
* myFuncB no longer lives in the IO monad. I wasn't sure if you specifically
wanted that, but now it can work with *any* instance of Failure.
* Since I assumed you ultimately wanted it to land in the IO monad, I
defined Exception instances. However, if you were dealing with a different
Failure instance (like [] or Maybe), these would be unncesary.
* I also assume that what you meant by "your code" and "their code" is that
you can modify your own code, but not theirs.
If you show me what the real code is you're working on, I'd be happy to more
fully develop a better solution with you. Anyway, here's the code.
Michael
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
import Control.Failure
import Data.Typeable (Typeable)
import Control.Exception (Exception)
-- Theirs (other library code stubs)
data TheirError = TheirErrorCase deriving Show
data TheirData = TheirData deriving Show
theirFunc :: [String] -> Either TheirError TheirData
theirFunc = undefined
-- Mine (my own code stubs)
data MyError = MyErrorCase deriving (Show, Typeable)
instance Exception MyError
deriving instance Typeable TheirError
instance Exception TheirError
data MyData = MyData deriving Show
myFuncA :: MonadFailure MyError m => TheirData -> m MyData
--myFuncA :: TheirData -> Either MyError MyData
myFuncA = undefined
myFuncB :: (MonadFailure MyError m, MonadFailure TheirError m)
=> m MyData
myFuncB = do
x <- try $ theirFunc []
myFuncA x
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091219/029b47b7/attachment.html
More information about the Haskell-Cafe
mailing list