| Copyright | (c) 2023-2025 Sayo contributors |
|---|---|
| License | MPL-2.0 (see the file LICENSE) |
| Maintainer | ymdfield@outlook.jp |
| Safe Haskell | None |
| Language | GHC2021 |
Data.Effect.Except
Description
An effect to escape from the normal control structure with an exception value in the middle of a context.
Synopsis
- throw :: forall e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Throw e :> es) => e -> a b
- catch :: forall b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Catch e :> es) => a b -> (e -> a b) -> a b
- withExcept :: forall e (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Catch e :> es, Throw e :> es, Applicative (Eff ff es), Free c ff) => Eff ff es a -> (e -> Eff ff es ()) -> Eff ff es a
- liftEither :: forall e (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Throw e :> es, Applicative (Eff ff es), Free c ff) => Either e a -> Eff ff es a
- joinEither :: forall e (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Throw e :> es, Monad (Eff ff es), Free c ff) => Eff ff es (Either e a) -> Eff ff es a
- joinExcept :: Monad m => Either (m a) a -> m a
- exc :: Monad m => m (Either (m a) a) -> m a
- onExcept :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Catch e :> es, Throw e :> es, Applicative (Eff ff es), Free c ff) => Eff ff es a -> Eff ff es () -> Eff ff es a
- runThrowIO :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Exception e, Monad (Eff ff es), Free c ff) => Eff ff (Throw e ': es) a -> Eff ff es a
- runCatchIO :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (UnliftIO :> es, Emb IO :> es, Exception e, Monad (Eff ff es), Free c ff) => Eff ff (Catch e ': es) a -> Eff ff es a
- throw' :: forall {k} (key :: k) e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (Throw e) es) => e -> a b
- throw'' :: forall {k} (tag :: k) e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (Throw e) :> es) => e -> a b
- throw'_ :: forall e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (Throw e) es) => e -> a b
- catch' :: forall {k} (key :: k) b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (Catch e) es) => a b -> (e -> a b) -> a b
- catch'' :: forall {k} (tag :: k) b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (Catch e) :> es) => a b -> (e -> a b) -> a b
- catch'_ :: forall b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (Catch e) es) => a b -> (e -> a b) -> a b
- data Catch e (a :: Type -> Type) b where
- data Throw e (a :: Type -> Type) b where
Documentation
throw :: forall e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Throw e :> es) => e -> a b Source #
catch :: forall b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Catch e :> es) => a b -> (e -> a b) -> a b Source #
Arguments
| :: forall e (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Catch e :> es, Throw e :> es, Applicative (Eff ff es), Free c ff) | |
| => Eff ff es a | Scope to which the exception handler applies |
| -> (e -> Eff ff es ()) | Exception handler |
| -> Eff ff es a |
If an exception occurs, executes the given exception handler, but the exception is not stopped there and is rethrown.
liftEither :: forall e (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Throw e :> es, Applicative (Eff ff es), Free c ff) => Either e a -> Eff ff es a Source #
joinEither :: forall e (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Throw e :> es, Monad (Eff ff es), Free c ff) => Eff ff es (Either e a) -> Eff ff es a Source #
Throws the result of the given action as an exception if it is Left.
joinExcept :: Monad m => Either (m a) a -> m a Source #
exc :: Monad m => m (Either (m a) a) -> m a Source #
If the result of the given action is Left, execute it as an action.
Arguments
| :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Catch e :> es, Throw e :> es, Applicative (Eff ff es), Free c ff) | |
| => Eff ff es a | Scope in which to detect exceptions |
| -> Eff ff es () | Action to execute in case of an exception |
| -> Eff ff es a |
If an exception occurs, executes the specified action, but the exception is not stopped there and is rethrown.
runThrowIO :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Exception e, Monad (Eff ff es), Free c ff) => Eff ff (Throw e ': es) a -> Eff ff es a Source #
Interpret the Throw effect based on an IO-fused semantics using IO-level exceptions.
runCatchIO :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (UnliftIO :> es, Emb IO :> es, Exception e, Monad (Eff ff es), Free c ff) => Eff ff (Catch e ': es) a -> Eff ff es a Source #
Interpret the Catch effect based on an IO-fused semantics using IO-level exceptions.
throw' :: forall {k} (key :: k) e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (Throw e) es) => e -> a b Source #
throw'' :: forall {k} (tag :: k) e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (Throw e) :> es) => e -> a b Source #
throw'_ :: forall e b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (Throw e) es) => e -> a b Source #
catch' :: forall {k} (key :: k) b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key (Catch e) es) => a b -> (e -> a b) -> a b Source #
catch'' :: forall {k} (tag :: k) b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag (Catch e) :> es) => a b -> (e -> a b) -> a b Source #
catch'_ :: forall b e a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In (Catch e) es) => a b -> (e -> a b) -> a b Source #
data Catch e (a :: Type -> Type) b where #
An effect to catch exceptions.
Constructors
| Catch | Catches exceptions within a scope and processes them according to the given exception handler. |
Instances
| PolyHFunctor (Catch e) | |
Defined in Data.Effect | |
| HFunctor (Catch e) | |
Defined in Data.Effect | |
| type FormOf (Catch e) | |
Defined in Data.Effect | |
| type LabelOf (Catch e) | |
Defined in Data.Effect | |
| type OrderOf (Catch e) | |
Defined in Data.Effect | |
data Throw e (a :: Type -> Type) b where #
An effect to escape from the normal control structure with an exception value of type e in the middle of a context.
Constructors
| Throw :: forall e (a :: Type -> Type) b. e -> Throw e a b | Throws an exception; that is, escapes from the normal control structure with an exception value in the middle of a context. |
Instances
| FirstOrder (Throw e) | |
Defined in Data.Effect | |
| PolyHFunctor (Throw e) | |
Defined in Data.Effect | |
| HFunctor (Throw e) | |
Defined in Data.Effect | |
| type FormOf (Throw e) | |
Defined in Data.Effect | |
| type LabelOf (Throw e) | |
Defined in Data.Effect | |
| type OrderOf (Throw e) | |
Defined in Data.Effect | |