Copyright | (c) Alexey Kuleshevich 2022-2023 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Fail e = FailT e Identity
- runFail :: (IsString e, Semigroup e) => Fail e a -> Either e a
- runFailLast :: IsString e => Fail e a -> Either e a
- runFailAgg :: Fail e a -> Either [e] a
- errorFail :: (Show e, HasCallStack) => Fail e a -> a
- errorFailWithoutStackTrace :: Show e => Fail e a -> a
- newtype FailT e m a = FailT (m (Either [e] a))
- data FailException where
- FailException :: (Typeable e, Show e) => {..} -> FailException
- failT :: Applicative m => e -> FailT e m a
- runFailT :: (IsString e, Semigroup e, Functor m) => FailT e m a -> m (Either e a)
- runFailLastT :: (IsString e, Functor m) => FailT e m a -> m (Either e a)
- runFailAggT :: FailT e m a -> m (Either [e] a)
- hoistFailT :: (forall a. m a -> n a) -> FailT e m b -> FailT e n b
- mapFailT :: (m (Either [e] a) -> n (Either [e] b)) -> FailT e m a -> FailT e n b
- mapErrorFailT :: Functor m => (e -> e') -> FailT e m a -> FailT e' m a
- mapErrorsFailT :: Functor m => ([e] -> [e']) -> FailT e m a -> FailT e' m a
- exceptFailT :: (HasCallStack, Typeable e, Show e, Monad m) => FailT e m a -> ExceptT FailException m a
- throwFailT :: (HasCallStack, Typeable e, Show e, MonadThrow m) => FailT e m a -> m a
- liftCatch :: (m (Either [e] a) -> (e -> m (Either [e] a)) -> m (Either [e] a)) -> FailT e m a -> (e -> FailT e m a) -> FailT e m a
- liftListen :: Monad m => (m (Either [e] a) -> m (Either [e] a, w)) -> FailT e m a -> FailT e m (a, w)
- liftPass :: Monad m => (m (Either [e] a, w -> w) -> m (Either [e] a)) -> FailT e m (a, w -> w) -> FailT e m a
Fail
runFail :: (IsString e, Semigroup e) => Fail e a -> Either e a Source #
Unwrap the pure Fail
monad and reveal the underlying result of monadic
computation.
>>>
runFail (fail "Something went wrong") :: Either String ()
Left "Something went wrong">>>
runFail (failT "Something went wrong" >> pure ())
Left "Something went wrong">>>
import Control.Applicative
>>>
runFail (failT "Something could have gone wrong" <|> pure ())
Right ()
All errors accrued during the monadic computation will be combined using the
Semigroup
instance and delimited by a comma:
>>>
runFail (fail "One thing went wrong" <|> fail "Another thing went wrong") :: Either String ()
Left "One thing went wrong, Another thing went wrong"
Failing with one of instances functions mempty
or empty
will yield a no-reason
error report:
>>>
runFail mempty :: Either String ()
Left "No failure reason given"
runFailLast :: IsString e => Fail e a -> Either e a Source #
This is a variant of runFailAgg
where only the error reported for the very last
failed computation will be produced and others discarded. This is useful when it is not
relevant to retain information about all the attempts and only the last one matters,
eg. parsing with backtracking.
runFailAgg :: Fail e a -> Either [e] a Source #
Convert a Fail
monad computation in an Either
, where the Left
will contain all
failures in the same order they where received, or Right
upon a successful computation.
>>>
runFailAgg (fail "One bad thing" <|> fail "Another bad thing") :: Either [String] ()
Left ["One bad thing","Another bad thing"]>>>
runFailAgg (fail "A bad thing" <|> pure "A good thing") :: Either [String] String
Right "A good thing"
errorFail :: (Show e, HasCallStack) => Fail e a -> a Source #
Throw an error if there was a failure, otherwise return the result of
computation. Use throwFailT
in case you'd like to handle an actual exception in some
other underlying monad.
>>>
errorFail (fail "This didn't work" :: Fail String ())
*** Exception: "This didn't work" CallStack (from HasCallStack): ...>>>
errorFail (fail "This didn't work" <|> pure "That Worked" :: Fail String String)
"That Worked"
errorFailWithoutStackTrace :: Show e => Fail e a -> a Source #
Same as errorFail
, but without the stack trace:
>>>
errorFailWithoutStackTrace (fail "This didn't work" :: Fail String ())
*** Exception: "This didn't work">>>
errorFailWithoutStackTrace (fail "This didn't work" <|> pure "That Worked" :: Fail String String)
"That Worked"
FailT
Fail monad transformer that plays well with MonadFail
type class.
Instances
(IsString e, MonadError e m) => MonadError e (FailT e m) Source # | |
Defined in Control.Monad.Trans.Fail throwError :: e -> FailT e m a # catchError :: FailT e m a -> (e -> FailT e m a) -> FailT e m a # | |
(IsString e, MonadReader r m) => MonadReader r (FailT e m) Source # | |
(IsString e, MonadState s m) => MonadState s (FailT e m) Source # | |
(IsString e, MonadWriter w m) => MonadWriter w (FailT e m) Source # | |
MonadTrans (FailT e) Source # | |
Defined in Control.Monad.Trans.Fail | |
(IsString e, Monad m) => MonadFail (FailT e m) Source # | |
Defined in Control.Monad.Trans.Fail | |
(IsString e, MonadIO m) => MonadIO (FailT e m) Source # | |
Defined in Control.Monad.Trans.Fail | |
(IsString e, MonadZip m) => MonadZip (FailT e m) Source # | |
Foldable f => Foldable (FailT e f) Source # | |
Defined in Control.Monad.Trans.Fail fold :: Monoid m => FailT e f m -> m # foldMap :: Monoid m => (a -> m) -> FailT e f a -> m # foldMap' :: Monoid m => (a -> m) -> FailT e f a -> m # foldr :: (a -> b -> b) -> b -> FailT e f a -> b # foldr' :: (a -> b -> b) -> b -> FailT e f a -> b # foldl :: (b -> a -> b) -> b -> FailT e f a -> b # foldl' :: (b -> a -> b) -> b -> FailT e f a -> b # foldr1 :: (a -> a -> a) -> FailT e f a -> a # foldl1 :: (a -> a -> a) -> FailT e f a -> a # toList :: FailT e f a -> [a] # length :: FailT e f a -> Int # elem :: Eq a => a -> FailT e f a -> Bool # maximum :: Ord a => FailT e f a -> a # minimum :: Ord a => FailT e f a -> a # | |
(Eq e, Eq1 m) => Eq1 (FailT e m) Source # | |
(Ord e, Ord1 m) => Ord1 (FailT e m) Source # | |
Defined in Control.Monad.Trans.Fail | |
(Read e, Read1 m) => Read1 (FailT e m) Source # | |
Defined in Control.Monad.Trans.Fail | |
(Show e, Show1 m) => Show1 (FailT e m) Source # | |
Contravariant f => Contravariant (FailT e f) Source # | |
Traversable f => Traversable (FailT e f) Source # | |
Defined in Control.Monad.Trans.Fail | |
Monad m => Alternative (FailT e m) Source # | Short-circuits on the first successful operation, combines failures otherwise. |
Monad m => Applicative (FailT e m) Source # | |
Functor m => Functor (FailT e m) Source # | |
(IsString e, Monad m) => Monad (FailT e m) Source # | Short-circuites on the first failing operation. |
(IsString e, MonadCont m) => MonadCont (FailT e m) Source # | |
(Monad m, Semigroup a) => Monoid (FailT e m a) Source # | |
(Monad m, Semigroup a) => Semigroup (FailT e m a) Source # | Executes all monadic actions and combines all successful results using a |
(Read e, Read1 m, Read a) => Read (FailT e m a) Source # | |
(Show e, Show1 m, Show a) => Show (FailT e m a) Source # | |
(Eq e, Eq1 m, Eq a) => Eq (FailT e m a) Source # | |
(Ord e, Ord1 m, Ord a) => Ord (FailT e m a) Source # | |
Defined in Control.Monad.Trans.Fail |
data FailException where Source #
An exception that is produced by the FailT
monad transformer.
FailException | |
|
Instances
Exception FailException Source # | |
Defined in Control.Monad.Trans.Fail | |
Show FailException Source # | |
Defined in Control.Monad.Trans.Fail showsPrec :: Int -> FailException -> ShowS # show :: FailException -> String # showList :: [FailException] -> ShowS # |
failT :: Applicative m => e -> FailT e m a Source #
runFailT :: (IsString e, Semigroup e, Functor m) => FailT e m a -> m (Either e a) Source #
Similar to runFail
, except underlying monad is not restricted to Identity
.
Unwrap the FailT
monad transformer and produce an action that can be executed in
the underlying monad and, which will produce either a comma delimited error message
upon a failure or the result otherwise.
>>>
runFailT (failT "Could have failed" <|> liftIO (putStrLn "Nothing went wrong"))
Nothing went wrong Right ()
runFailLastT :: (IsString e, Functor m) => FailT e m a -> m (Either e a) Source #
Similar to runFailLast
, except underlying monad is not restricted to Identity
.
runFailAggT :: FailT e m a -> m (Either [e] a) Source #
Similar to runFailAgg
, except underlying monad is not restricted to Identity
.
hoistFailT :: (forall a. m a -> n a) -> FailT e m b -> FailT e n b Source #
Change the underlying monad with the hoisting function.
mapFailT :: (m (Either [e] a) -> n (Either [e] b)) -> FailT e m a -> FailT e n b Source #
Map a function over the underlying representation of the FailT
monad.
mapErrorFailT :: Functor m => (e -> e') -> FailT e m a -> FailT e' m a Source #
Map a function over the error type in the FailT
monad.
mapErrorsFailT :: Functor m => ([e] -> [e']) -> FailT e m a -> FailT e' m a Source #
Map a function over the aggregation of errors in the FailT
monad. Could be used for
example for clearing our all of the aggregated error messages:
>>>
runFail (mapErrorsFailT (const []) $ failT "Something went wrong") :: Either String ()
Left "No failure reason given"
exceptFailT :: (HasCallStack, Typeable e, Show e, Monad m) => FailT e m a -> ExceptT FailException m a Source #
throwFailT :: (HasCallStack, Typeable e, Show e, MonadThrow m) => FailT e m a -> m a Source #
Use the MonadThrow
instance to raise a FailException
in the underlying monad.
>>>
throwFailT (failT "One thing went wrong")
*** Exception: FailException "One thing went wrong" ...>>>
throwFailT (failT "One thing went wrong") :: Maybe ()
Nothing
Helpers
liftCatch :: (m (Either [e] a) -> (e -> m (Either [e] a)) -> m (Either [e] a)) -> FailT e m a -> (e -> FailT e m a) -> FailT e m a Source #
Lift a
operation to the new monad.catchE