{-# LANGUAGE BlockArguments, DerivingVia #-}
module Control.Effect.Alt
(
Alt(..)
, Alternative(..)
, runAltMaybe
, altToError
, altToNonDet
, altToErrorSimple
, ErrorThreads
, AltMaybeC
, InterpretAltC(..)
, InterpretAltReifiedC
, AltToNonDetC
, InterpretAltSimpleC(..)
) where
import Control.Applicative
import Control.Monad
import Control.Effect
import Control.Effect.Carrier
import Control.Effect.Error
import Control.Effect.NonDet
import Control.Effect.Type.Alt
import Control.Effect.Internal.Utils
import Control.Effect.Internal.Error
import Control.Effect.Carrier.Internal.Compose
import Control.Effect.Carrier.Internal.Interpret
import Control.Effect.Carrier.Internal.Intro
import Control.Monad.Trans.Except
import Control.Monad.Trans.Identity
newtype InterpretAltC h m a = InterpretAltC {
InterpretAltC h m a -> InterpretC h Alt m a
unInterpretAltC :: InterpretC h Alt m a
}
deriving ( a -> InterpretAltC h m b -> InterpretAltC h m a
(a -> b) -> InterpretAltC h m a -> InterpretAltC h m b
(forall a b.
(a -> b) -> InterpretAltC h m a -> InterpretAltC h m b)
-> (forall a b. a -> InterpretAltC h m b -> InterpretAltC h m a)
-> Functor (InterpretAltC h m)
forall a b. a -> InterpretAltC h m b -> InterpretAltC h m a
forall a b. (a -> b) -> InterpretAltC h m a -> InterpretAltC h m b
forall h (m :: * -> *) a b.
Functor m =>
a -> InterpretAltC h m b -> InterpretAltC h m a
forall h (m :: * -> *) a b.
Functor m =>
(a -> b) -> InterpretAltC h m a -> InterpretAltC h m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> InterpretAltC h m b -> InterpretAltC h m a
$c<$ :: forall h (m :: * -> *) a b.
Functor m =>
a -> InterpretAltC h m b -> InterpretAltC h m a
fmap :: (a -> b) -> InterpretAltC h m a -> InterpretAltC h m b
$cfmap :: forall h (m :: * -> *) a b.
Functor m =>
(a -> b) -> InterpretAltC h m a -> InterpretAltC h m b
Functor, Functor (InterpretAltC h m)
a -> InterpretAltC h m a
Functor (InterpretAltC h m)
-> (forall a. a -> InterpretAltC h m a)
-> (forall a b.
InterpretAltC h m (a -> b)
-> InterpretAltC h m a -> InterpretAltC h m b)
-> (forall a b c.
(a -> b -> c)
-> InterpretAltC h m a
-> InterpretAltC h m b
-> InterpretAltC h m c)
-> (forall a b.
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b)
-> (forall a b.
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m a)
-> Applicative (InterpretAltC h m)
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m a
InterpretAltC h m (a -> b)
-> InterpretAltC h m a -> InterpretAltC h m b
(a -> b -> c)
-> InterpretAltC h m a
-> InterpretAltC h m b
-> InterpretAltC h m c
forall a. a -> InterpretAltC h m a
forall a b.
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m a
forall a b.
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
forall a b.
InterpretAltC h m (a -> b)
-> InterpretAltC h m a -> InterpretAltC h m b
forall a b c.
(a -> b -> c)
-> InterpretAltC h m a
-> InterpretAltC h m b
-> InterpretAltC h m c
forall h (m :: * -> *).
Applicative m =>
Functor (InterpretAltC h m)
forall h (m :: * -> *) a. Applicative m => a -> InterpretAltC h m a
forall h (m :: * -> *) a b.
Applicative m =>
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m a
forall h (m :: * -> *) a b.
Applicative m =>
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
forall h (m :: * -> *) a b.
Applicative m =>
InterpretAltC h m (a -> b)
-> InterpretAltC h m a -> InterpretAltC h m b
forall h (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> InterpretAltC h m a
-> InterpretAltC h m b
-> InterpretAltC h m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m a
$c<* :: forall h (m :: * -> *) a b.
Applicative m =>
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m a
*> :: InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
$c*> :: forall h (m :: * -> *) a b.
Applicative m =>
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
liftA2 :: (a -> b -> c)
-> InterpretAltC h m a
-> InterpretAltC h m b
-> InterpretAltC h m c
$cliftA2 :: forall h (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> InterpretAltC h m a
-> InterpretAltC h m b
-> InterpretAltC h m c
<*> :: InterpretAltC h m (a -> b)
-> InterpretAltC h m a -> InterpretAltC h m b
$c<*> :: forall h (m :: * -> *) a b.
Applicative m =>
InterpretAltC h m (a -> b)
-> InterpretAltC h m a -> InterpretAltC h m b
pure :: a -> InterpretAltC h m a
$cpure :: forall h (m :: * -> *) a. Applicative m => a -> InterpretAltC h m a
$cp1Applicative :: forall h (m :: * -> *).
Applicative m =>
Functor (InterpretAltC h m)
Applicative, Applicative (InterpretAltC h m)
a -> InterpretAltC h m a
Applicative (InterpretAltC h m)
-> (forall a b.
InterpretAltC h m a
-> (a -> InterpretAltC h m b) -> InterpretAltC h m b)
-> (forall a b.
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b)
-> (forall a. a -> InterpretAltC h m a)
-> Monad (InterpretAltC h m)
InterpretAltC h m a
-> (a -> InterpretAltC h m b) -> InterpretAltC h m b
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
forall a. a -> InterpretAltC h m a
forall a b.
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
forall a b.
InterpretAltC h m a
-> (a -> InterpretAltC h m b) -> InterpretAltC h m b
forall h (m :: * -> *). Monad m => Applicative (InterpretAltC h m)
forall h (m :: * -> *) a. Monad m => a -> InterpretAltC h m a
forall h (m :: * -> *) a b.
Monad m =>
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
forall h (m :: * -> *) a b.
Monad m =>
InterpretAltC h m a
-> (a -> InterpretAltC h m b) -> InterpretAltC h m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> InterpretAltC h m a
$creturn :: forall h (m :: * -> *) a. Monad m => a -> InterpretAltC h m a
>> :: InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
$c>> :: forall h (m :: * -> *) a b.
Monad m =>
InterpretAltC h m a -> InterpretAltC h m b -> InterpretAltC h m b
>>= :: InterpretAltC h m a
-> (a -> InterpretAltC h m b) -> InterpretAltC h m b
$c>>= :: forall h (m :: * -> *) a b.
Monad m =>
InterpretAltC h m a
-> (a -> InterpretAltC h m b) -> InterpretAltC h m b
$cp1Monad :: forall h (m :: * -> *). Monad m => Applicative (InterpretAltC h m)
Monad
, Monad (InterpretAltC h m)
Monad (InterpretAltC h m)
-> (forall a. (a -> InterpretAltC h m a) -> InterpretAltC h m a)
-> MonadFix (InterpretAltC h m)
(a -> InterpretAltC h m a) -> InterpretAltC h m a
forall a. (a -> InterpretAltC h m a) -> InterpretAltC h m a
forall h (m :: * -> *). MonadFix m => Monad (InterpretAltC h m)
forall h (m :: * -> *) a.
MonadFix m =>
(a -> InterpretAltC h m a) -> InterpretAltC h m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> InterpretAltC h m a) -> InterpretAltC h m a
$cmfix :: forall h (m :: * -> *) a.
MonadFix m =>
(a -> InterpretAltC h m a) -> InterpretAltC h m a
$cp1MonadFix :: forall h (m :: * -> *). MonadFix m => Monad (InterpretAltC h m)
MonadFix, Monad (InterpretAltC h m)
Monad (InterpretAltC h m)
-> (forall a. IO a -> InterpretAltC h m a)
-> MonadIO (InterpretAltC h m)
IO a -> InterpretAltC h m a
forall a. IO a -> InterpretAltC h m a
forall h (m :: * -> *). MonadIO m => Monad (InterpretAltC h m)
forall h (m :: * -> *) a. MonadIO m => IO a -> InterpretAltC h m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> InterpretAltC h m a
$cliftIO :: forall h (m :: * -> *) a. MonadIO m => IO a -> InterpretAltC h m a
$cp1MonadIO :: forall h (m :: * -> *). MonadIO m => Monad (InterpretAltC h m)
MonadIO, Monad (InterpretAltC h m)
Monad (InterpretAltC h m)
-> (forall a. String -> InterpretAltC h m a)
-> MonadFail (InterpretAltC h m)
String -> InterpretAltC h m a
forall a. String -> InterpretAltC h m a
forall h (m :: * -> *). MonadFail m => Monad (InterpretAltC h m)
forall h (m :: * -> *) a.
MonadFail m =>
String -> InterpretAltC h m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> InterpretAltC h m a
$cfail :: forall h (m :: * -> *) a.
MonadFail m =>
String -> InterpretAltC h m a
$cp1MonadFail :: forall h (m :: * -> *). MonadFail m => Monad (InterpretAltC h m)
MonadFail
, Monad (InterpretAltC h m)
e -> InterpretAltC h m a
Monad (InterpretAltC h m)
-> (forall e a. Exception e => e -> InterpretAltC h m a)
-> MonadThrow (InterpretAltC h m)
forall e a. Exception e => e -> InterpretAltC h m a
forall h (m :: * -> *). MonadThrow m => Monad (InterpretAltC h m)
forall h (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> InterpretAltC h m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> InterpretAltC h m a
$cthrowM :: forall h (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> InterpretAltC h m a
$cp1MonadThrow :: forall h (m :: * -> *). MonadThrow m => Monad (InterpretAltC h m)
MonadThrow, MonadThrow (InterpretAltC h m)
MonadThrow (InterpretAltC h m)
-> (forall e a.
Exception e =>
InterpretAltC h m a
-> (e -> InterpretAltC h m a) -> InterpretAltC h m a)
-> MonadCatch (InterpretAltC h m)
InterpretAltC h m a
-> (e -> InterpretAltC h m a) -> InterpretAltC h m a
forall e a.
Exception e =>
InterpretAltC h m a
-> (e -> InterpretAltC h m a) -> InterpretAltC h m a
forall h (m :: * -> *).
MonadCatch m =>
MonadThrow (InterpretAltC h m)
forall h (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
InterpretAltC h m a
-> (e -> InterpretAltC h m a) -> InterpretAltC h m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: InterpretAltC h m a
-> (e -> InterpretAltC h m a) -> InterpretAltC h m a
$ccatch :: forall h (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
InterpretAltC h m a
-> (e -> InterpretAltC h m a) -> InterpretAltC h m a
$cp1MonadCatch :: forall h (m :: * -> *).
MonadCatch m =>
MonadThrow (InterpretAltC h m)
MonadCatch, MonadCatch (InterpretAltC h m)
MonadCatch (InterpretAltC h m)
-> (forall b.
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b)
-> (forall b.
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b)
-> (forall a b c.
InterpretAltC h m a
-> (a -> ExitCase b -> InterpretAltC h m c)
-> (a -> InterpretAltC h m b)
-> InterpretAltC h m (b, c))
-> MonadMask (InterpretAltC h m)
InterpretAltC h m a
-> (a -> ExitCase b -> InterpretAltC h m c)
-> (a -> InterpretAltC h m b)
-> InterpretAltC h m (b, c)
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
forall b.
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
forall a b c.
InterpretAltC h m a
-> (a -> ExitCase b -> InterpretAltC h m c)
-> (a -> InterpretAltC h m b)
-> InterpretAltC h m (b, c)
forall h (m :: * -> *).
MonadMask m =>
MonadCatch (InterpretAltC h m)
forall h (m :: * -> *) b.
MonadMask m =>
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
forall h (m :: * -> *) a b c.
MonadMask m =>
InterpretAltC h m a
-> (a -> ExitCase b -> InterpretAltC h m c)
-> (a -> InterpretAltC h m b)
-> InterpretAltC h m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: InterpretAltC h m a
-> (a -> ExitCase b -> InterpretAltC h m c)
-> (a -> InterpretAltC h m b)
-> InterpretAltC h m (b, c)
$cgeneralBracket :: forall h (m :: * -> *) a b c.
MonadMask m =>
InterpretAltC h m a
-> (a -> ExitCase b -> InterpretAltC h m c)
-> (a -> InterpretAltC h m b)
-> InterpretAltC h m (b, c)
uninterruptibleMask :: ((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
$cuninterruptibleMask :: forall h (m :: * -> *) b.
MonadMask m =>
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
mask :: ((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
$cmask :: forall h (m :: * -> *) b.
MonadMask m =>
((forall a. InterpretAltC h m a -> InterpretAltC h m a)
-> InterpretAltC h m b)
-> InterpretAltC h m b
$cp1MonadMask :: forall h (m :: * -> *).
MonadMask m =>
MonadCatch (InterpretAltC h m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> InterpretAltC h m a
(forall (m :: * -> *) a. Monad m => m a -> InterpretAltC h m a)
-> MonadTrans (InterpretAltC h)
forall h (m :: * -> *) a. Monad m => m a -> InterpretAltC h m a
forall (m :: * -> *) a. Monad m => m a -> InterpretAltC h m a
forall (t :: (* -> *) -> * -> *).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> InterpretAltC h m a
$clift :: forall h (m :: * -> *) a. Monad m => m a -> InterpretAltC h m a
MonadTrans, MonadTrans (InterpretAltC h)
m (StT (InterpretAltC h) a) -> InterpretAltC h m a
MonadTrans (InterpretAltC h)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (InterpretAltC h) -> m a) -> InterpretAltC h m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (InterpretAltC h) a) -> InterpretAltC h m a)
-> MonadTransControl (InterpretAltC h)
(Run (InterpretAltC h) -> m a) -> InterpretAltC h m a
forall h. MonadTrans (InterpretAltC h)
forall h (m :: * -> *) a.
Monad m =>
m (StT (InterpretAltC h) a) -> InterpretAltC h m a
forall h (m :: * -> *) a.
Monad m =>
(Run (InterpretAltC h) -> m a) -> InterpretAltC h m a
forall (m :: * -> *) a.
Monad m =>
m (StT (InterpretAltC h) a) -> InterpretAltC h m a
forall (m :: * -> *) a.
Monad m =>
(Run (InterpretAltC h) -> m a) -> InterpretAltC h m a
forall (t :: (* -> *) -> * -> *).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (InterpretAltC h) a) -> InterpretAltC h m a
$crestoreT :: forall h (m :: * -> *) a.
Monad m =>
m (StT (InterpretAltC h) a) -> InterpretAltC h m a
liftWith :: (Run (InterpretAltC h) -> m a) -> InterpretAltC h m a
$cliftWith :: forall h (m :: * -> *) a.
Monad m =>
(Run (InterpretAltC h) -> m a) -> InterpretAltC h m a
$cp1MonadTransControl :: forall h. MonadTrans (InterpretAltC h)
MonadTransControl)
newtype InterpretAltSimpleC m a = InterpretAltSimpleC {
InterpretAltSimpleC m a -> InterpretSimpleC Alt m a
unInterpretAltSimpleC :: InterpretSimpleC Alt m a
}
deriving ( a -> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
(a -> b) -> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
(forall a b.
(a -> b) -> InterpretAltSimpleC m a -> InterpretAltSimpleC m b)
-> (forall a b.
a -> InterpretAltSimpleC m b -> InterpretAltSimpleC m a)
-> Functor (InterpretAltSimpleC m)
forall a b. a -> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
forall a b.
(a -> b) -> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
forall (m :: * -> *) a b.
Functor m =>
a -> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
fmap :: (a -> b) -> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
Functor, Functor (InterpretAltSimpleC m)
a -> InterpretAltSimpleC m a
Functor (InterpretAltSimpleC m)
-> (forall a. a -> InterpretAltSimpleC m a)
-> (forall a b.
InterpretAltSimpleC m (a -> b)
-> InterpretAltSimpleC m a -> InterpretAltSimpleC m b)
-> (forall a b c.
(a -> b -> c)
-> InterpretAltSimpleC m a
-> InterpretAltSimpleC m b
-> InterpretAltSimpleC m c)
-> (forall a b.
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b)
-> (forall a b.
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m a)
-> Applicative (InterpretAltSimpleC m)
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
InterpretAltSimpleC m (a -> b)
-> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
(a -> b -> c)
-> InterpretAltSimpleC m a
-> InterpretAltSimpleC m b
-> InterpretAltSimpleC m c
forall a. a -> InterpretAltSimpleC m a
forall a b.
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
forall a b.
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
forall a b.
InterpretAltSimpleC m (a -> b)
-> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
forall a b c.
(a -> b -> c)
-> InterpretAltSimpleC m a
-> InterpretAltSimpleC m b
-> InterpretAltSimpleC m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (m :: * -> *).
Applicative m =>
Functor (InterpretAltSimpleC m)
forall (m :: * -> *) a.
Applicative m =>
a -> InterpretAltSimpleC m a
forall (m :: * -> *) a b.
Applicative m =>
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
forall (m :: * -> *) a b.
Applicative m =>
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
forall (m :: * -> *) a b.
Applicative m =>
InterpretAltSimpleC m (a -> b)
-> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> InterpretAltSimpleC m a
-> InterpretAltSimpleC m b
-> InterpretAltSimpleC m c
<* :: InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m a
*> :: InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
liftA2 :: (a -> b -> c)
-> InterpretAltSimpleC m a
-> InterpretAltSimpleC m b
-> InterpretAltSimpleC m c
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> InterpretAltSimpleC m a
-> InterpretAltSimpleC m b
-> InterpretAltSimpleC m c
<*> :: InterpretAltSimpleC m (a -> b)
-> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
InterpretAltSimpleC m (a -> b)
-> InterpretAltSimpleC m a -> InterpretAltSimpleC m b
pure :: a -> InterpretAltSimpleC m a
$cpure :: forall (m :: * -> *) a.
Applicative m =>
a -> InterpretAltSimpleC m a
$cp1Applicative :: forall (m :: * -> *).
Applicative m =>
Functor (InterpretAltSimpleC m)
Applicative, Applicative (InterpretAltSimpleC m)
a -> InterpretAltSimpleC m a
Applicative (InterpretAltSimpleC m)
-> (forall a b.
InterpretAltSimpleC m a
-> (a -> InterpretAltSimpleC m b) -> InterpretAltSimpleC m b)
-> (forall a b.
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b)
-> (forall a. a -> InterpretAltSimpleC m a)
-> Monad (InterpretAltSimpleC m)
InterpretAltSimpleC m a
-> (a -> InterpretAltSimpleC m b) -> InterpretAltSimpleC m b
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
forall a. a -> InterpretAltSimpleC m a
forall a b.
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
forall a b.
InterpretAltSimpleC m a
-> (a -> InterpretAltSimpleC m b) -> InterpretAltSimpleC m b
forall (m :: * -> *).
Monad m =>
Applicative (InterpretAltSimpleC m)
forall (m :: * -> *) a. Monad m => a -> InterpretAltSimpleC m a
forall (m :: * -> *) a b.
Monad m =>
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
forall (m :: * -> *) a b.
Monad m =>
InterpretAltSimpleC m a
-> (a -> InterpretAltSimpleC m b) -> InterpretAltSimpleC m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> InterpretAltSimpleC m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> InterpretAltSimpleC m a
>> :: InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
InterpretAltSimpleC m a
-> InterpretAltSimpleC m b -> InterpretAltSimpleC m b
>>= :: InterpretAltSimpleC m a
-> (a -> InterpretAltSimpleC m b) -> InterpretAltSimpleC m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
InterpretAltSimpleC m a
-> (a -> InterpretAltSimpleC m b) -> InterpretAltSimpleC m b
$cp1Monad :: forall (m :: * -> *).
Monad m =>
Applicative (InterpretAltSimpleC m)
Monad
, Monad (InterpretAltSimpleC m)
Monad (InterpretAltSimpleC m)
-> (forall a.
(a -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a)
-> MonadFix (InterpretAltSimpleC m)
(a -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
forall a. (a -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
forall (m :: * -> *). MonadFix m => Monad (InterpretAltSimpleC m)
forall (m :: * -> *) a.
MonadFix m =>
(a -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
mfix :: (a -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
$cmfix :: forall (m :: * -> *) a.
MonadFix m =>
(a -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
$cp1MonadFix :: forall (m :: * -> *). MonadFix m => Monad (InterpretAltSimpleC m)
MonadFix, Monad (InterpretAltSimpleC m)
Monad (InterpretAltSimpleC m)
-> (forall a. IO a -> InterpretAltSimpleC m a)
-> MonadIO (InterpretAltSimpleC m)
IO a -> InterpretAltSimpleC m a
forall a. IO a -> InterpretAltSimpleC m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall (m :: * -> *). MonadIO m => Monad (InterpretAltSimpleC m)
forall (m :: * -> *) a.
MonadIO m =>
IO a -> InterpretAltSimpleC m a
liftIO :: IO a -> InterpretAltSimpleC m a
$cliftIO :: forall (m :: * -> *) a.
MonadIO m =>
IO a -> InterpretAltSimpleC m a
$cp1MonadIO :: forall (m :: * -> *). MonadIO m => Monad (InterpretAltSimpleC m)
MonadIO, Monad (InterpretAltSimpleC m)
Monad (InterpretAltSimpleC m)
-> (forall a. String -> InterpretAltSimpleC m a)
-> MonadFail (InterpretAltSimpleC m)
String -> InterpretAltSimpleC m a
forall a. String -> InterpretAltSimpleC m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
forall (m :: * -> *). MonadFail m => Monad (InterpretAltSimpleC m)
forall (m :: * -> *) a.
MonadFail m =>
String -> InterpretAltSimpleC m a
fail :: String -> InterpretAltSimpleC m a
$cfail :: forall (m :: * -> *) a.
MonadFail m =>
String -> InterpretAltSimpleC m a
$cp1MonadFail :: forall (m :: * -> *). MonadFail m => Monad (InterpretAltSimpleC m)
MonadFail
, Monad (InterpretAltSimpleC m)
e -> InterpretAltSimpleC m a
Monad (InterpretAltSimpleC m)
-> (forall e a. Exception e => e -> InterpretAltSimpleC m a)
-> MonadThrow (InterpretAltSimpleC m)
forall e a. Exception e => e -> InterpretAltSimpleC m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall (m :: * -> *). MonadThrow m => Monad (InterpretAltSimpleC m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> InterpretAltSimpleC m a
throwM :: e -> InterpretAltSimpleC m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> InterpretAltSimpleC m a
$cp1MonadThrow :: forall (m :: * -> *). MonadThrow m => Monad (InterpretAltSimpleC m)
MonadThrow, MonadThrow (InterpretAltSimpleC m)
MonadThrow (InterpretAltSimpleC m)
-> (forall e a.
Exception e =>
InterpretAltSimpleC m a
-> (e -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a)
-> MonadCatch (InterpretAltSimpleC m)
InterpretAltSimpleC m a
-> (e -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
forall e a.
Exception e =>
InterpretAltSimpleC m a
-> (e -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
forall (m :: * -> *).
MonadCatch m =>
MonadThrow (InterpretAltSimpleC m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
InterpretAltSimpleC m a
-> (e -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
catch :: InterpretAltSimpleC m a
-> (e -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
InterpretAltSimpleC m a
-> (e -> InterpretAltSimpleC m a) -> InterpretAltSimpleC m a
$cp1MonadCatch :: forall (m :: * -> *).
MonadCatch m =>
MonadThrow (InterpretAltSimpleC m)
MonadCatch, MonadCatch (InterpretAltSimpleC m)
MonadCatch (InterpretAltSimpleC m)
-> (forall b.
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b)
-> (forall b.
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b)
-> (forall a b c.
InterpretAltSimpleC m a
-> (a -> ExitCase b -> InterpretAltSimpleC m c)
-> (a -> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m (b, c))
-> MonadMask (InterpretAltSimpleC m)
InterpretAltSimpleC m a
-> (a -> ExitCase b -> InterpretAltSimpleC m c)
-> (a -> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m (b, c)
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
forall b.
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
forall a b c.
InterpretAltSimpleC m a
-> (a -> ExitCase b -> InterpretAltSimpleC m c)
-> (a -> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
forall (m :: * -> *).
MonadMask m =>
MonadCatch (InterpretAltSimpleC m)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
forall (m :: * -> *) a b c.
MonadMask m =>
InterpretAltSimpleC m a
-> (a -> ExitCase b -> InterpretAltSimpleC m c)
-> (a -> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m (b, c)
generalBracket :: InterpretAltSimpleC m a
-> (a -> ExitCase b -> InterpretAltSimpleC m c)
-> (a -> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m (b, c)
$cgeneralBracket :: forall (m :: * -> *) a b c.
MonadMask m =>
InterpretAltSimpleC m a
-> (a -> ExitCase b -> InterpretAltSimpleC m c)
-> (a -> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m (b, c)
uninterruptibleMask :: ((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
$cuninterruptibleMask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
mask :: ((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
$cmask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. InterpretAltSimpleC m a -> InterpretAltSimpleC m a)
-> InterpretAltSimpleC m b)
-> InterpretAltSimpleC m b
$cp1MonadMask :: forall (m :: * -> *).
MonadMask m =>
MonadCatch (InterpretAltSimpleC m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving m a -> InterpretAltSimpleC m a
(forall (m :: * -> *) a. Monad m => m a -> InterpretAltSimpleC m a)
-> MonadTrans InterpretAltSimpleC
forall (m :: * -> *) a. Monad m => m a -> InterpretAltSimpleC m a
forall (t :: (* -> *) -> * -> *).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> InterpretAltSimpleC m a
$clift :: forall (m :: * -> *) a. Monad m => m a -> InterpretAltSimpleC m a
MonadTrans
type InterpretAltReifiedC m a =
forall s
. ReifiesHandler s Alt m
=> InterpretAltC (ViaReifiedH s) m a
deriving newtype instance Handler h Alt m => Carrier (InterpretAltC h m)
deriving via Effly (InterpretAltC h m)
instance Handler h Alt m => Alternative (InterpretAltC h m)
instance Handler h Alt m => MonadPlus (InterpretAltC h m)
deriving newtype instance
(Monad m, Carrier (InterpretSimpleC Alt m))
=> Carrier (InterpretAltSimpleC m)
deriving via Effly (InterpretAltSimpleC m)
instance (Monad m, Carrier (InterpretSimpleC Alt m))
=> Alternative (InterpretAltSimpleC m)
instance (Monad m, Carrier (InterpretSimpleC Alt m))
=> MonadPlus (InterpretAltSimpleC m)
data AltToErrorUnitH
instance Eff (Error ()) m
=> Handler AltToErrorUnitH Alt m where
effHandler :: Alt (Effly z) x -> Effly z x
effHandler = \case
Alt (Effly z) x
Empty -> () -> Effly z x
forall e (m :: * -> *) a. Eff (Throw e) m => e -> m a
throw ()
Alt Effly z x
ma Effly z x
mb -> Effly z x
ma Effly z x -> (() -> Effly z x) -> Effly z x
forall e (m :: * -> *) a.
Eff (Catch e) m =>
m a -> (e -> m a) -> m a
`catch` \() -> Effly z x
mb
{-# INLINEABLE effHandler #-}
type AltMaybeC = CompositionC
'[ IntroUnderC Alt '[Catch (), Throw ()]
, InterpretAltC AltToErrorUnitH
, ErrorC ()
]
runAltMaybe :: forall m a p
. ( Threaders '[ErrorThreads] m p
, Carrier m
)
=> AltMaybeC m a
-> m (Maybe a)
runAltMaybe :: AltMaybeC m a -> m (Maybe a)
runAltMaybe =
(Either () a -> Maybe a) -> m (Either () a) -> m (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((() -> Maybe a) -> (a -> Maybe a) -> Either () a -> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> () -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) a -> Maybe a
forall a. a -> Maybe a
Just)
(m (Either () a) -> m (Maybe a))
-> (ErrorC () m a -> m (Either () a))
-> ErrorC () m a
-> m (Maybe a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# ErrorC () m a -> m (Either () a)
forall e (m :: * -> *) a (p :: [(* -> *) -> * -> *]).
(Carrier m, Threaders '[ErrorThreads] m p) =>
ErrorC e m a -> m (Either e a)
runError
(ErrorC () m a -> m (Maybe a))
-> (InterpretC AltToErrorUnitH Alt (ErrorC () m) a
-> ErrorC () m a)
-> InterpretC AltToErrorUnitH Alt (ErrorC () m) a
-> m (Maybe a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC AltToErrorUnitH Alt (ErrorC () m) a -> ErrorC () m a
forall h (e :: (* -> *) -> * -> *) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC AltToErrorUnitH Alt (ErrorC () m) a -> m (Maybe a))
-> (InterpretAltC AltToErrorUnitH (ErrorC () m) a
-> InterpretC AltToErrorUnitH Alt (ErrorC () m) a)
-> InterpretAltC AltToErrorUnitH (ErrorC () m) a
-> m (Maybe a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretAltC AltToErrorUnitH (ErrorC () m) a
-> InterpretC AltToErrorUnitH Alt (ErrorC () m) a
forall h (m :: * -> *) a.
InterpretAltC h m a -> InterpretC h Alt m a
unInterpretAltC
(InterpretAltC AltToErrorUnitH (ErrorC () m) a -> m (Maybe a))
-> (IntroUnderC
Alt
'[Catch (), Throw ()]
(InterpretAltC AltToErrorUnitH (ErrorC () m))
a
-> InterpretAltC AltToErrorUnitH (ErrorC () m) a)
-> IntroUnderC
Alt
'[Catch (), Throw ()]
(InterpretAltC AltToErrorUnitH (ErrorC () m))
a
-> m (Maybe a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# IntroUnderC
Alt
'[Catch (), Throw ()]
(InterpretAltC AltToErrorUnitH (ErrorC () m))
a
-> InterpretAltC AltToErrorUnitH (ErrorC () m) a
forall (new :: [(* -> *) -> * -> *]) (e :: (* -> *) -> * -> *)
(m :: * -> *) a.
(KnownList new, IntroConsistent '[e] new m) =>
IntroUnderC e new m a -> m a
introUnder
(IntroUnderC
Alt
'[Catch (), Throw ()]
(InterpretAltC AltToErrorUnitH (ErrorC () m))
a
-> m (Maybe a))
-> (AltMaybeC m a
-> IntroUnderC
Alt
'[Catch (), Throw ()]
(InterpretAltC AltToErrorUnitH (ErrorC () m))
a)
-> AltMaybeC m a
-> m (Maybe a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# AltMaybeC m a
-> IntroUnderC
Alt
'[Catch (), Throw ()]
(InterpretAltC AltToErrorUnitH (ErrorC () m))
a
forall (ts :: [(* -> *) -> * -> *]) (m :: * -> *) a.
CompositionC ts m a -> CompositionBaseM ts m a
runComposition
{-# INLINE runAltMaybe #-}
altToError :: forall e m a
. Eff (Error e) m
=> e
-> InterpretAltReifiedC m a
-> m a
altToError :: e -> InterpretAltReifiedC m a -> m a
altToError e
e InterpretAltReifiedC m a
m =
EffHandler Alt m -> InterpretReifiedC Alt m a -> m a
forall (e :: (* -> *) -> * -> *) (m :: * -> *) a.
(RepresentationalEff e, Carrier m) =>
EffHandler e m -> InterpretReifiedC e m a -> m a
interpret \case
Alt (Effly z) x
Empty -> e -> Effly z x
forall e (m :: * -> *) a. Eff (Throw e) m => e -> m a
throw e
e
Alt ma mb -> Effly z x
ma Effly z x -> (e -> Effly z x) -> Effly z x
forall e (m :: * -> *) a.
Eff (Catch e) m =>
m a -> (e -> m a) -> m a
`catch` \(e
_ :: e) -> Effly z x
mb
(InterpretReifiedC Alt m a -> m a)
-> InterpretReifiedC Alt m a -> m a
forall a b. (a -> b) -> a -> b
$ InterpretAltC (ViaReifiedH s) m a
-> InterpretC (ViaReifiedH s) Alt m a
forall h (m :: * -> *) a.
InterpretAltC h m a -> InterpretC h Alt m a
unInterpretAltC
(InterpretAltC (ViaReifiedH s) m a
-> InterpretC (ViaReifiedH s) Alt m a)
-> InterpretAltC (ViaReifiedH s) m a
-> InterpretC (ViaReifiedH s) Alt m a
forall a b. (a -> b) -> a -> b
$ InterpretAltC (ViaReifiedH s) m a
InterpretAltReifiedC m a
m
{-# INLINE altToError #-}
data AltToNonDetH
instance Eff NonDet m => Handler AltToNonDetH Alt m where
effHandler :: Alt (Effly z) x -> Effly z x
effHandler = \case
Alt (Effly z) x
Empty -> Effly z x
forall (m :: * -> *) a. Eff NonDet m => m a
lose
Alt Effly z x
ma Effly z x
mb -> Effly z x -> Effly z x -> Effly z x
forall (m :: * -> *) a. Eff NonDet m => m a -> m a -> m a
choose Effly z x
ma Effly z x
mb
{-# INLINEABLE effHandler #-}
type AltToNonDetC = InterpretAltC AltToNonDetH
altToNonDet :: Eff NonDet m
=> AltToNonDetC m a
-> m a
altToNonDet :: AltToNonDetC m a -> m a
altToNonDet = InterpretC AltToNonDetH Alt m a -> m a
forall h (e :: (* -> *) -> * -> *) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler (InterpretC AltToNonDetH Alt m a -> m a)
-> (AltToNonDetC m a -> InterpretC AltToNonDetH Alt m a)
-> AltToNonDetC m a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# AltToNonDetC m a -> InterpretC AltToNonDetH Alt m a
forall h (m :: * -> *) a.
InterpretAltC h m a -> InterpretC h Alt m a
unInterpretAltC
{-# INLINE altToNonDet #-}
altToErrorSimple :: forall e m a p
. ( Eff (Error e) m
, Threaders '[ReaderThreads] m p
)
=> e
-> InterpretAltSimpleC m a
-> m a
altToErrorSimple :: e -> InterpretAltSimpleC m a -> m a
altToErrorSimple e
e =
EffHandler Alt m -> InterpretSimpleC Alt m a -> m a
forall (e :: (* -> *) -> * -> *) (m :: * -> *) a
(p :: [(* -> *) -> * -> *]).
(RepresentationalEff e, Threaders '[ReaderThreads] m p,
Carrier m) =>
EffHandler e m -> InterpretSimpleC e m a -> m a
interpretSimple \case
Alt (Effly z) x
Empty -> e -> Effly z x
forall e (m :: * -> *) a. Eff (Throw e) m => e -> m a
throw e
e
Alt ma mb -> Effly z x
ma Effly z x -> (e -> Effly z x) -> Effly z x
forall e (m :: * -> *) a.
Eff (Catch e) m =>
m a -> (e -> m a) -> m a
`catch` \(e
_ :: e) -> Effly z x
mb
(InterpretSimpleC Alt m a -> m a)
-> (InterpretAltSimpleC m a -> InterpretSimpleC Alt m a)
-> InterpretAltSimpleC m a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretAltSimpleC m a -> InterpretSimpleC Alt m a
forall (m :: * -> *) a.
InterpretAltSimpleC m a -> InterpretSimpleC Alt m a
unInterpretAltSimpleC
{-# INLINE altToErrorSimple #-}