{- | An effect for polymorphic failure.

Predefined carriers:

* "Control.Carrier.Throw.Either"
* "Control.Carrier.Error.Either" (with 'Control.Effect.Catch.Catch')

@since 1.0.0.0
-}
module Control.Effect.Throw
( -- * Throw effect
  Throw(..)
, throwError
, liftEither
  -- * Re-exports
, Algebra
, Has
, run
) where

import Control.Algebra
import Control.Effect.Throw.Internal (Throw(..))

-- | Throw an error, escaping the current computation up to the nearest 'Control.Effect.Catch.catchError' (if any).
--
-- @since 0.1.0.0
throwError :: Has (Throw e) sig m => e -> m a
throwError :: e -> m a
throwError = Throw e m a -> m a
forall (eff :: (* -> *) -> * -> *) (sig :: (* -> *) -> * -> *)
       (m :: * -> *) a.
(Member eff sig, Algebra sig m) =>
eff m a -> m a
send (Throw e m a -> m a) -> (e -> Throw e m a) -> e -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Throw e m a
forall e (m :: * -> *) a. e -> Throw e m a
Throw
{-# INLINE throwError #-}

-- | Lifts an @'Either' e@ into Monad m with effect @'Throw' e@
--
-- @since 1.1.0.0
liftEither :: Has (Throw e) sig m => Either e a -> m a
liftEither :: Either e a -> m a
liftEither = (e -> m a) -> (a -> m a) -> Either e a -> m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either e -> m a
forall e (sig :: (* -> *) -> * -> *) (m :: * -> *) a.
Has (Throw e) sig m =>
e -> m a
throwError a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return