Created
January 6, 2017 03:15
-
-
Save berdario/c7a640d4c45c973fef1960b121d8cc95 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DeriveFunctor #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
module Example where | |
import Control.Exception | |
import Control.Monad | |
import Control.Monad.Error.Class | |
import Control.Monad.Trans.Except | |
import Data.Void | |
import UnexceptionalIO | |
class (MonadError SomeException m) => Eff1 m where | |
f1 :: String -> m String | |
class Eff2 m where | |
f2 :: (MonadError e m) => String -> m String | |
class Eff3 m where | |
f3 :: String -> m String | |
type AppM = ExceptT SomeException UIO | |
appReadFile :: String -> AppM String | |
appReadFile = ExceptT . fromIO . readFile | |
instance Eff1 AppM where | |
f1 = appReadFile | |
data MockIO1a a = MockIO1a a deriving (Functor) | |
instance Applicative MockIO1a where | |
pure = MockIO1a | |
(<*>) (MockIO1a f) = fmap f | |
instance Monad MockIO1a where | |
(MockIO1a a) >>= f = f a | |
instance MonadError SomeException MockIO1a where | |
throwError = undefined | |
catchError = const | |
instance Eff1 MockIO1a where | |
f1 = return | |
-- MockIO1a's throwError should never happen, but still it's not nice to have to use undefined. | |
-- I hoped I could use Void: | |
-- data MockIO1b a = MockIO1b (Either Void a) deriving (Functor) | |
-- instance (MonadError SomeException MockIO1b) where | |
-- throwError = absurd -- doesn't compile. | |
-- Maybe it could, if I wouldn't have to specialize (MonadError e) to (MonadError SomeException) | |
-- catchError = const | |
-- instance Eff1 MockIO1b where | |
-- f1 = pure | |
instance Eff2 AppM where | |
f2 = appReadFile | |
data MockIO2 a = MockIO2 a deriving (Functor) | |
instance Applicative MockIO2 where | |
pure = MockIO2 | |
(<*>) (MockIO2 f) = fmap f | |
instance Eff2 MockIO2 where | |
f2 = pure | |
instance Eff3 AppM where | |
f3 = appReadFile | |
instance Eff3 MockIO2 where | |
f3 = pure |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment