문제

I spend half of my day trying to figure out how to use EitherT as a way to deal with errors in my code.

I have defined a transformer stack like this.

-- Stuff Monad

data StuffConfig = StuffConfig {
  appId     :: T.Text,
  appSecret :: T.Text
}

data StuffState = StuffState {
  stateToken :: Maybe Token,
  stateTime  :: POSIXTime
}

newtype Stuff a = Stuff {
  runStuff :: (ReaderT StuffConfig (StateT StuffState (EitherT T.Text IO))) a
} deriving (Monad, Functor, Applicative, 
            MonadIO, 
            MonadReader StuffConfig,
            MonadState StuffState
            )



askStuff :: StuffConfig -> Stuff a -> IO (Either T.Text a)
askStuff config a = do
  t <- getPOSIXTime 
  runEitherT (evalStateT (runReaderT (runStuff a) config) (StuffState Nothing t))

This works quite well as long as i only use the ReaderT and StateT functions. I am under the impression that now i should be able to write something like this:

faultyFunction :: String -> Stuff String
faultyFunction s = do
  when s == "left" $ left "breaking out"
  "right"

More important is capturing Either return values which should be possible with hoistEither from the errors package:

faultyLookup :: Map -> String -> Stuff String
faultyLookup m k = do
  hoistEither $ lookup k m

I read the real world haskell chapter on monad transformers and fiddled around with lift. But I can't get anything to typecheck.

도움이 되었습니까?

해결책

The reason you can't just use the left and hoistEither functions directly is that unlike StateT and ReaderT from the mtl package, the either package doesn't provide a typeclass similar to MonadReader or MonadState.

The aforementioned typeclasses take care of lifting in the monad stack transparently, but for EitherT, you have to do the lifting yourself (or write a MonadEither typeclass similar to MonadReader et al).

faultyFunction :: String -> Stuff String
faultyFunction s = do
  when (s == "left") $ Stuff $ lift $ lift $ left "breaking out"
  return "right"

First you need to apply the Stuff wrapper, then lift over the ReaderT transformer and then lift again over the StateT transformer.

You probably want to write utility functions for yourself such as

stuffLeft :: T.Text -> Stuff a
stuffLeft = Stuff . lift . lift . left

Then you can simply use it like this:

faultyFunction :: String -> Stuff String
faultyFunction s = do
  when (s == "left") $ stuffLeft "breaking out"
  return "right"

Alternatively, you could use Control.Monad.Error from mtl, if you define an Error instance for Text.

instance Error T.Text where
  strMsg = T.pack

Now you can change the definition of Stuff implement left and hoistEither like this:

newtype Stuff a = Stuff {
  runStuff :: (ReaderT StuffConfig (StateT StuffState (ErrorT T.Text IO))) a
} deriving (Monad, Functor, Applicative,
            MonadIO,
            MonadReader StuffConfig,
            MonadState StuffState,
            MonadError T.Text
            )

left :: T.Text -> Stuff a
left = throwError

hoistEither :: Either T.Text a -> Stuff a
hoistEither = Stuff . lift . lift . ErrorT . return

With this your original faultyFunction type-checks without any manual lifting.

You can also write generic implementations for left and hoistEither which work for any instance of MonadError (using either from Data.Either):

left :: MonadError e m => e -> m a
left = throwError

hoistEither :: MonadError e m => Either e a -> m a
hoistEither = either throwError return

다른 팁

Just to add to shang's answer: MonadError is basically the corresponding type class to EitherT. You can add its instance for EitherT (for some reason it's commented out in the either library):

import Control.Monad.Trans.Either
  hiding (left, right, hoistEither)

instance Monad m => MonadError e (EitherT e m) where
  throwError = EitherT . return . Left
  EitherT m `catchError` h = EitherT $ m >>= \a -> case a of
    Left  l -> runEitherT (h l)
    Right r -> return (Right r)

Then, define your own methods that are generalized to MonadError:

left :: MonadError e m => e -> m a
left = throwError
{-# INLINE left #-}

right :: MonadError e m => a -> m a
right = return
{-# INLINE right #-}

hoistEither :: MonadError e m => Either e a -> m a
hoistEither (Left a)  = throwError a
hoistEither (Right e) = return e
{-# INLINE hoistEither #-}

Now you can do things like:

import qualified Data.Map as Map

newtype Stuff a = Stuff {
  runStuff :: (ReaderT Int (StateT Char (EitherT T.Text IO))) a
} deriving (Monad, Functor,
            MonadReader Int,
            MonadError T.Text, -- <--- MonadError instance
            MonadState Char
            )


faultyLookup :: (Ord k) => Map.Map k a -> k -> Stuff a
faultyLookup m k =
  maybe (left $ T.pack "Lookup error") right $ Map.lookup k m

or generalize it to

faultyLookup :: (MonadError T.Text m, Ord k) => Map.Map k a -> k -> m a
faultyLookup m k =
  maybe (left $ T.pack "Lookup error") right $ Map.lookup k m
라이센스 : CC-BY-SA ~와 함께 속성
제휴하지 않습니다 StackOverflow
scroll top