module Effectful.NonDet
(
NonDet(..)
, OnEmptyPolicy(..)
, runNonDet
, emptyEff
, sumEff
, Alternative(..)
, HasCallStack
, CallStack
, getCallStack
, prettyCallStack
) where
import Control.Applicative
import Data.Coerce
import GHC.Generics
import GHC.Stack
import Effectful
import Effectful.Dispatch.Dynamic
import Effectful.Dispatch.Static
import Effectful.Dispatch.Static.Primitive
import Effectful.Error.Static
import Effectful.Internal.Monad (LocalEnv(..), NonDet(..))
data OnEmptyPolicy
= OnEmptyKeep
| OnEmptyRollback
deriving stock (OnEmptyPolicy -> OnEmptyPolicy -> Bool
(OnEmptyPolicy -> OnEmptyPolicy -> Bool)
-> (OnEmptyPolicy -> OnEmptyPolicy -> Bool) -> Eq OnEmptyPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
== :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
$c/= :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
/= :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
Eq, (forall x. OnEmptyPolicy -> Rep OnEmptyPolicy x)
-> (forall x. Rep OnEmptyPolicy x -> OnEmptyPolicy)
-> Generic OnEmptyPolicy
forall x. Rep OnEmptyPolicy x -> OnEmptyPolicy
forall x. OnEmptyPolicy -> Rep OnEmptyPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OnEmptyPolicy -> Rep OnEmptyPolicy x
from :: forall x. OnEmptyPolicy -> Rep OnEmptyPolicy x
$cto :: forall x. Rep OnEmptyPolicy x -> OnEmptyPolicy
to :: forall x. Rep OnEmptyPolicy x -> OnEmptyPolicy
Generic, Eq OnEmptyPolicy
Eq OnEmptyPolicy =>
(OnEmptyPolicy -> OnEmptyPolicy -> Ordering)
-> (OnEmptyPolicy -> OnEmptyPolicy -> Bool)
-> (OnEmptyPolicy -> OnEmptyPolicy -> Bool)
-> (OnEmptyPolicy -> OnEmptyPolicy -> Bool)
-> (OnEmptyPolicy -> OnEmptyPolicy -> Bool)
-> (OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy)
-> (OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy)
-> Ord OnEmptyPolicy
OnEmptyPolicy -> OnEmptyPolicy -> Bool
OnEmptyPolicy -> OnEmptyPolicy -> Ordering
OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OnEmptyPolicy -> OnEmptyPolicy -> Ordering
compare :: OnEmptyPolicy -> OnEmptyPolicy -> Ordering
$c< :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
< :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
$c<= :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
<= :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
$c> :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
> :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
$c>= :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
>= :: OnEmptyPolicy -> OnEmptyPolicy -> Bool
$cmax :: OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy
max :: OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy
$cmin :: OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy
min :: OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy
Ord, Int -> OnEmptyPolicy -> ShowS
[OnEmptyPolicy] -> ShowS
OnEmptyPolicy -> String
(Int -> OnEmptyPolicy -> ShowS)
-> (OnEmptyPolicy -> String)
-> ([OnEmptyPolicy] -> ShowS)
-> Show OnEmptyPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OnEmptyPolicy -> ShowS
showsPrec :: Int -> OnEmptyPolicy -> ShowS
$cshow :: OnEmptyPolicy -> String
show :: OnEmptyPolicy -> String
$cshowList :: [OnEmptyPolicy] -> ShowS
showList :: [OnEmptyPolicy] -> ShowS
Show)
runNonDet
:: HasCallStack
=> OnEmptyPolicy
-> Eff (NonDet : es) a
-> Eff es (Either CallStack a)
runNonDet :: forall (es :: [(Type -> Type) -> Type -> Type]) a.
HasCallStack =>
OnEmptyPolicy -> Eff (NonDet : es) a -> Eff es (Either CallStack a)
runNonDet = \case
OnEmptyPolicy
OnEmptyKeep -> Eff (NonDet : es) a -> Eff es (Either CallStack a)
forall (es :: [(Type -> Type) -> Type -> Type]) a.
HasCallStack =>
Eff (NonDet : es) a -> Eff es (Either CallStack a)
runNonDetKeep
OnEmptyPolicy
OnEmptyRollback -> Eff (NonDet : es) a -> Eff es (Either CallStack a)
forall (es :: [(Type -> Type) -> Type -> Type]) a.
HasCallStack =>
Eff (NonDet : es) a -> Eff es (Either CallStack a)
runNonDetRollback
runNonDetKeep
:: HasCallStack
=> Eff (NonDet : es) a
-> Eff es (Either CallStack a)
runNonDetKeep :: forall (es :: [(Type -> Type) -> Type -> Type]) a.
HasCallStack =>
Eff (NonDet : es) a -> Eff es (Either CallStack a)
runNonDetKeep = (Eff (Error ErrorEmpty : es) a -> Eff es (Either CallStack a))
-> (forall {a} {localEs :: [(Type -> Type) -> Type -> Type]}.
(HasCallStack, NonDet :> localEs) =>
LocalEnv localEs (Error ErrorEmpty : es)
-> NonDet (Eff localEs) a -> Eff (Error ErrorEmpty : es) a)
-> Eff (NonDet : es) a
-> Eff es (Either CallStack a)
forall (e :: (Type -> Type) -> Type -> Type)
(handlerEs :: [(Type -> Type) -> Type -> Type]) a
(es :: [(Type -> Type) -> Type -> Type]) b.
(HasCallStack, DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret ((Either (CallStack, ErrorEmpty) a -> Either CallStack a)
-> Eff es (Either (CallStack, ErrorEmpty) a)
-> Eff es (Either CallStack a)
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Either (CallStack, ErrorEmpty) a -> Either CallStack a
forall cs e a. Either (cs, e) a -> Either cs a
noError (Eff es (Either (CallStack, ErrorEmpty) a)
-> Eff es (Either CallStack a))
-> (Eff (Error ErrorEmpty : es) a
-> Eff es (Either (CallStack, ErrorEmpty) a))
-> Eff (Error ErrorEmpty : es) a
-> Eff es (Either CallStack a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (es :: [(Type -> Type) -> Type -> Type]) a.
HasCallStack =>
Eff (Error e : es) a -> Eff es (Either (CallStack, e) a)
runError @ErrorEmpty) ((forall {a} {localEs :: [(Type -> Type) -> Type -> Type]}.
(HasCallStack, NonDet :> localEs) =>
LocalEnv localEs (Error ErrorEmpty : es)
-> NonDet (Eff localEs) a -> Eff (Error ErrorEmpty : es) a)
-> Eff (NonDet : es) a -> Eff es (Either CallStack a))
-> (forall {a} {localEs :: [(Type -> Type) -> Type -> Type]}.
(HasCallStack, NonDet :> localEs) =>
LocalEnv localEs (Error ErrorEmpty : es)
-> NonDet (Eff localEs) a -> Eff (Error ErrorEmpty : es) a)
-> Eff (NonDet : es) a
-> Eff es (Either CallStack a)
forall a b. (a -> b) -> a -> b
$ \LocalEnv localEs (Error ErrorEmpty : es)
env -> \case
NonDet (Eff localEs) a
Empty -> ErrorEmpty -> Eff (Error ErrorEmpty : es) a
forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, Error e :> es, Show e) =>
e -> Eff es a
throwError ErrorEmpty
ErrorEmpty
Eff localEs a
m1 :<|>: Eff localEs a
m2 -> LocalEnv localEs (Error ErrorEmpty : es)
-> ((forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r)
-> Eff (Error ErrorEmpty : es) a)
-> Eff (Error ErrorEmpty : es) a
forall (es :: [(Type -> Type) -> Type -> Type])
(handlerEs :: [(Type -> Type) -> Type -> Type])
(localEs :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, SharedSuffix es handlerEs) =>
LocalEnv localEs handlerEs
-> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) -> Eff es a
localSeqUnlift LocalEnv localEs (Error ErrorEmpty : es)
env (((forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r)
-> Eff (Error ErrorEmpty : es) a)
-> Eff (Error ErrorEmpty : es) a)
-> ((forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r)
-> Eff (Error ErrorEmpty : es) a)
-> Eff (Error ErrorEmpty : es) a
forall a b. (a -> b) -> a -> b
$ \forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r
unlift -> do
Maybe a
mr <- (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a)
-> Eff (Error ErrorEmpty : es) a
-> Eff (Error ErrorEmpty : es) (Maybe a)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Eff localEs a -> Eff (Error ErrorEmpty : es) a
forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r
unlift Eff localEs a
m1) Eff (Error ErrorEmpty : es) (Maybe a)
-> (CallStack
-> ErrorEmpty -> Eff (Error ErrorEmpty : es) (Maybe a))
-> Eff (Error ErrorEmpty : es) (Maybe a)
forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, Error e :> es) =>
Eff es a -> (CallStack -> e -> Eff es a) -> Eff es a
`catchError` \CallStack
_ ErrorEmpty
ErrorEmpty -> Maybe a -> Eff (Error ErrorEmpty : es) (Maybe a)
forall a. a -> Eff (Error ErrorEmpty : es) a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
case Maybe a
mr of
Just a
r -> a -> Eff (Error ErrorEmpty : es) a
forall a. a -> Eff (Error ErrorEmpty : es) a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure a
r
Maybe a
Nothing -> Eff localEs a -> Eff (Error ErrorEmpty : es) a
forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r
unlift Eff localEs a
m2
runNonDetRollback
:: HasCallStack
=> Eff (NonDet : es) a
-> Eff es (Either CallStack a)
runNonDetRollback :: forall (es :: [(Type -> Type) -> Type -> Type]) a.
HasCallStack =>
Eff (NonDet : es) a -> Eff es (Either CallStack a)
runNonDetRollback = (Eff (Error ErrorEmpty : es) a -> Eff es (Either CallStack a))
-> (forall {a} {localEs :: [(Type -> Type) -> Type -> Type]}.
(HasCallStack, NonDet :> localEs) =>
LocalEnv localEs (Error ErrorEmpty : es)
-> NonDet (Eff localEs) a -> Eff (Error ErrorEmpty : es) a)
-> Eff (NonDet : es) a
-> Eff es (Either CallStack a)
forall (e :: (Type -> Type) -> Type -> Type)
(handlerEs :: [(Type -> Type) -> Type -> Type]) a
(es :: [(Type -> Type) -> Type -> Type]) b.
(HasCallStack, DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret Eff (Error ErrorEmpty : es) a -> Eff es (Either CallStack a)
forall {es :: [(Type -> Type) -> Type -> Type]} {b}.
Eff (Error ErrorEmpty : es) b -> Eff es (Either CallStack b)
setup ((forall {a} {localEs :: [(Type -> Type) -> Type -> Type]}.
(HasCallStack, NonDet :> localEs) =>
LocalEnv localEs (Error ErrorEmpty : es)
-> NonDet (Eff localEs) a -> Eff (Error ErrorEmpty : es) a)
-> Eff (NonDet : es) a -> Eff es (Either CallStack a))
-> (forall {a} {localEs :: [(Type -> Type) -> Type -> Type]}.
(HasCallStack, NonDet :> localEs) =>
LocalEnv localEs (Error ErrorEmpty : es)
-> NonDet (Eff localEs) a -> Eff (Error ErrorEmpty : es) a)
-> Eff (NonDet : es) a
-> Eff es (Either CallStack a)
forall a b. (a -> b) -> a -> b
$ \LocalEnv localEs (Error ErrorEmpty : es)
env -> \case
NonDet (Eff localEs) a
Empty -> ErrorEmpty -> Eff (Error ErrorEmpty : es) a
forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, Error e :> es, Show e) =>
e -> Eff es a
throwError ErrorEmpty
ErrorEmpty
Eff localEs a
m1 :<|>: Eff localEs a
m2 -> do
LocalEnv localEs (Error ErrorEmpty : es)
backupEnv <- LocalEnv localEs (Error ErrorEmpty : es)
-> Eff
(Error ErrorEmpty : es) (LocalEnv localEs (Error ErrorEmpty : es))
forall (localEs :: [(Type -> Type) -> Type -> Type])
(handlerEs :: [(Type -> Type) -> Type -> Type])
(es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
LocalEnv localEs handlerEs -> Eff es (LocalEnv localEs handlerEs)
cloneLocalEnv LocalEnv localEs (Error ErrorEmpty : es)
env
LocalEnv localEs (Error ErrorEmpty : es)
-> ((forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r)
-> Eff (Error ErrorEmpty : es) a)
-> Eff (Error ErrorEmpty : es) a
forall (es :: [(Type -> Type) -> Type -> Type])
(handlerEs :: [(Type -> Type) -> Type -> Type])
(localEs :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, SharedSuffix es handlerEs) =>
LocalEnv localEs handlerEs
-> ((forall r. Eff localEs r -> Eff es r) -> Eff es a) -> Eff es a
localSeqUnlift LocalEnv localEs (Error ErrorEmpty : es)
env (((forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r)
-> Eff (Error ErrorEmpty : es) a)
-> Eff (Error ErrorEmpty : es) a)
-> ((forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r)
-> Eff (Error ErrorEmpty : es) a)
-> Eff (Error ErrorEmpty : es) a
forall a b. (a -> b) -> a -> b
$ \forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r
unlift -> do
Maybe a
mr <- (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a)
-> Eff (Error ErrorEmpty : es) a
-> Eff (Error ErrorEmpty : es) (Maybe a)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Eff localEs a -> Eff (Error ErrorEmpty : es) a
forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r
unlift Eff localEs a
m1) Eff (Error ErrorEmpty : es) (Maybe a)
-> (CallStack
-> ErrorEmpty -> Eff (Error ErrorEmpty : es) (Maybe a))
-> Eff (Error ErrorEmpty : es) (Maybe a)
forall e (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, Error e :> es) =>
Eff es a -> (CallStack -> e -> Eff es a) -> Eff es a
`catchError` \CallStack
_ ErrorEmpty
ErrorEmpty -> do
LocalEnv localEs (Error ErrorEmpty : es)
-> LocalEnv localEs (Error ErrorEmpty : es)
-> Eff (Error ErrorEmpty : es) ()
forall (localEs :: [(Type -> Type) -> Type -> Type])
(handlerEs :: [(Type -> Type) -> Type -> Type])
(es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
LocalEnv localEs handlerEs
-> LocalEnv localEs handlerEs -> Eff es ()
restoreLocalEnv LocalEnv localEs (Error ErrorEmpty : es)
env LocalEnv localEs (Error ErrorEmpty : es)
backupEnv
Maybe a -> Eff (Error ErrorEmpty : es) (Maybe a)
forall a. a -> Eff (Error ErrorEmpty : es) a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
case Maybe a
mr of
Just a
r -> a -> Eff (Error ErrorEmpty : es) a
forall a. a -> Eff (Error ErrorEmpty : es) a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure a
r
Maybe a
Nothing -> Eff localEs a -> Eff (Error ErrorEmpty : es) a
forall {r}. Eff localEs r -> Eff (Error ErrorEmpty : es) r
unlift Eff localEs a
m2
where
setup :: Eff (Error ErrorEmpty : es) b -> Eff es (Either CallStack b)
setup Eff (Error ErrorEmpty : es) b
action = do
Env es
backupEs <- (Env es -> IO (Env es)) -> Eff es (Env es)
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Env es -> IO a) -> Eff es a
unsafeEff Env es -> IO (Env es)
forall (es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
Env es -> IO (Env es)
cloneEnv
forall e (es :: [(Type -> Type) -> Type -> Type]) a.
HasCallStack =>
Eff (Error e : es) a -> Eff es (Either (CallStack, e) a)
runError @ErrorEmpty Eff (Error ErrorEmpty : es) b
action Eff es (Either (CallStack, ErrorEmpty) b)
-> (Either (CallStack, ErrorEmpty) b
-> Eff es (Either CallStack b))
-> Eff es (Either CallStack b)
forall a b. Eff es a -> (a -> Eff es b) -> Eff es b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right b
r -> Either CallStack b -> Eff es (Either CallStack b)
forall a. a -> Eff es a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Either CallStack b -> Eff es (Either CallStack b))
-> Either CallStack b -> Eff es (Either CallStack b)
forall a b. (a -> b) -> a -> b
$ b -> Either CallStack b
forall a b. b -> Either a b
Right b
r
Left (CallStack
cs, ErrorEmpty
_) -> do
(Env es -> IO ()) -> Eff es ()
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(Env es -> IO a) -> Eff es a
unsafeEff ((Env es -> IO ()) -> Eff es ()) -> (Env es -> IO ()) -> Eff es ()
forall a b. (a -> b) -> a -> b
$ \Env es
es -> Env es -> Env es -> IO ()
forall (es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
Env es -> Env es -> IO ()
restoreEnv Env es
es Env es
backupEs
Either CallStack b -> Eff es (Either CallStack b)
forall a. a -> Eff es a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Either CallStack b -> Eff es (Either CallStack b))
-> Either CallStack b -> Eff es (Either CallStack b)
forall a b. (a -> b) -> a -> b
$ CallStack -> Either CallStack b
forall a b. a -> Either a b
Left CallStack
cs
emptyEff :: (HasCallStack, NonDet :> es) => Eff es a
emptyEff :: forall (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, NonDet :> es) =>
Eff es a
emptyEff = (HasCallStack => NonDet (Eff es) a -> Eff es a)
-> NonDet (Eff es) a -> Eff es a
forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack HasCallStack => NonDet (Eff es) a -> Eff es a
NonDet (Eff es) a -> Eff es a
forall (e :: (Type -> Type) -> Type -> Type)
(es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send NonDet (Eff es) a
forall (a :: Type -> Type) b. NonDet a b
Empty
sumEff :: (HasCallStack, Foldable t, NonDet :> es) => t (Eff es a) -> Eff es a
sumEff :: forall (t :: Type -> Type) (es :: [(Type -> Type) -> Type -> Type])
a.
(HasCallStack, Foldable t, NonDet :> es) =>
t (Eff es a) -> Eff es a
sumEff = (Eff es a -> Eff es a -> Eff es a)
-> Eff es a -> t (Eff es a) -> Eff es a
forall a b. (a -> b -> b) -> b -> t a -> b
forall (t :: Type -> Type) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Eff es a -> Eff es a -> Eff es a
forall a. Eff es a -> Eff es a -> Eff es a
forall (f :: Type -> Type) a. Alternative f => f a -> f a -> f a
(<|>) Eff es a
forall (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, NonDet :> es) =>
Eff es a
emptyEff
data ErrorEmpty = ErrorEmpty
instance Show ErrorEmpty where
show :: ErrorEmpty -> String
show ErrorEmpty
ErrorEmpty = String
"Effectful.NonDet.ErrorEmpty"
noError :: Either (cs, e) a -> Either cs a
noError :: forall cs e a. Either (cs, e) a -> Either cs a
noError = ((cs, e) -> Either cs a)
-> (a -> Either cs a) -> Either (cs, e) a -> Either cs a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (cs -> Either cs a
forall a b. a -> Either a b
Left (cs -> Either cs a) -> ((cs, e) -> cs) -> (cs, e) -> Either cs a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (cs, e) -> cs
forall a b. (a, b) -> a
fst) a -> Either cs a
forall a b. b -> Either a b
Right
cloneLocalEnv
:: HasCallStack
=> LocalEnv localEs handlerEs
-> Eff es (LocalEnv localEs handlerEs)
cloneLocalEnv :: forall (localEs :: [(Type -> Type) -> Type -> Type])
(handlerEs :: [(Type -> Type) -> Type -> Type])
(es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
LocalEnv localEs handlerEs -> Eff es (LocalEnv localEs handlerEs)
cloneLocalEnv = Eff es (Env localEs) -> Eff es (LocalEnv localEs handlerEs)
forall a b. Coercible a b => a -> b
coerce (Eff es (Env localEs) -> Eff es (LocalEnv localEs handlerEs))
-> (LocalEnv localEs handlerEs -> Eff es (Env localEs))
-> LocalEnv localEs handlerEs
-> Eff es (LocalEnv localEs handlerEs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Env localEs) -> Eff es (Env localEs)
forall a (es :: [(Type -> Type) -> Type -> Type]). IO a -> Eff es a
unsafeEff_ (IO (Env localEs) -> Eff es (Env localEs))
-> (LocalEnv localEs handlerEs -> IO (Env localEs))
-> LocalEnv localEs handlerEs
-> Eff es (Env localEs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Env localEs -> IO (Env localEs)
forall (es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
Env es -> IO (Env es)
cloneEnv (Env localEs -> IO (Env localEs))
-> (LocalEnv localEs handlerEs -> Env localEs)
-> LocalEnv localEs handlerEs
-> IO (Env localEs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LocalEnv localEs handlerEs -> Env localEs
forall a b. Coercible a b => a -> b
coerce
restoreLocalEnv
:: HasCallStack
=> LocalEnv localEs handlerEs
-> LocalEnv localEs handlerEs
-> Eff es ()
restoreLocalEnv :: forall (localEs :: [(Type -> Type) -> Type -> Type])
(handlerEs :: [(Type -> Type) -> Type -> Type])
(es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
LocalEnv localEs handlerEs
-> LocalEnv localEs handlerEs -> Eff es ()
restoreLocalEnv LocalEnv localEs handlerEs
dest LocalEnv localEs handlerEs
src = IO () -> Eff es ()
forall a (es :: [(Type -> Type) -> Type -> Type]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> IO () -> Eff es ()
forall a b. (a -> b) -> a -> b
$ Env localEs -> Env localEs -> IO ()
forall (es :: [(Type -> Type) -> Type -> Type]).
HasCallStack =>
Env es -> Env es -> IO ()
restoreEnv (LocalEnv localEs handlerEs -> Env localEs
forall a b. Coercible a b => a -> b
coerce LocalEnv localEs handlerEs
dest) (LocalEnv localEs handlerEs -> Env localEs
forall a b. Coercible a b => a -> b
coerce LocalEnv localEs handlerEs
src)