{-# LANGUAGE CPP #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Control.Monad.Trans.Result
(
type T.Result
, pattern Result
, runResult
, pattern Error
, pattern Success
, result
, fromEither
, toEither
, fromSuccess
, toMonadFail
, type T.ResultT
, pattern ResultT
, runResultT
, mapResultT
, T.throwE
, T.catchE
, T.liftCallCC
, T.liftListen
, T.liftPass
) where
import Control.Monad.Trans.Except (ExceptT (ExceptT), runExcept, runExceptT)
import qualified Control.Monad.Trans.Except.Result as T
import Data.Functor.Identity (Identity (runIdentity))
import qualified GHC.Show as S
import Text.Read (Read (readPrec))
import qualified Text.Read as R
import qualified Text.Read.Lex as R
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail (MonadFail)
#endif
instance {-# OVERLAPPING #-} Show a => Show (T.Result a) where
showsPrec d (Error e) = showParen (S.appPrec < d) $ showString "Error " . showsPrec S.appPrec1 e
showsPrec d (Success a) = showParen (S.appPrec < d) $ showString "Success " . showsPrec S.appPrec1 a
instance {-# OVERLAPPING #-} Read a => Read (T.Result a) where
readPrec =
R.parens $
R.prec S.appPrec (
do
R.lift $ R.expect $ R.Ident "Error"
e <- R.step readPrec
pure $ Error e
)
R.+++
R.prec S.appPrec (
do
R.lift $ R.expect $ R.Ident "Success"
a <- R.step readPrec
pure $ Success a
)
instance Semigroup (T.Result a) where
Error _ <> a = a
a <> _ = a
{-# INLINE (<>) #-}
instance Monoid (T.Result a) where
mempty = Error "mempty"
{-# INLINE mempty #-}
mappend = (<>)
{-# INLINE mappend #-}
pattern Result :: Either String a -> T.Result a
pattern Result r <- (runIdentity . runExceptT . T.runResultT -> r)
where Result r = T.ResultT $ ExceptT $ pure r
runResult :: T.Result a -> Either String a
runResult = runExcept . T.runResult
{-# INLINE runResult #-}
pattern Error :: String -> T.Result a
pattern Error e = Result (Left e)
pattern Success :: a -> T.Result a
pattern Success a = Result (Right a)
{-# COMPLETE Error, Success #-}
result :: (String -> b) -> (a -> b) -> T.Result a -> b
result f _ (Error e) = f e
result _ g (Success a) = g a
{-# INLINE result #-}
fromEither :: Either String a -> T.Result a
fromEither = Result
{-# INLINE fromEither #-}
toEither :: T.Result a -> Either String a
toEither = runResult
{-# INLINE toEither #-}
fromSuccess :: a -> T.Result a -> a
fromSuccess _ (Success a) = a
fromSuccess a _ = a
{-# INLINE fromSuccess #-}
toMonadFail :: MonadFail m => T.Result a -> m a
toMonadFail (Success a) = pure a
toMonadFail (Error e) = fail e
{-# INLINE toMonadFail #-}
pattern ResultT :: Functor m => m (T.Result a) -> T.ResultT m a
pattern ResultT m <- ((Result <$>) . runExceptT . T.runResultT -> m)
where ResultT m = T.ResultT $ ExceptT $ runResult <$> m
{-# COMPLETE ResultT #-}
runResultT :: Functor m => T.ResultT m a -> m (T.Result a)
runResultT (ResultT m) = m
{-# INLINE runResultT #-}
mapResultT :: (Functor m, Functor n) => (m (T.Result a) -> n (T.Result b)) -> T.ResultT m a -> T.ResultT n b
mapResultT f = T.mapResultT $ T.runResultT . ResultT . f . runResultT . T.ResultT
{-# INLINE mapResultT #-}