module Effectful.Provider
(
Provider
, Provider_
, runProvider
, runProvider_
, provide
, provide_
, provideWith
, provideWith_
) where
import Control.Monad
import Data.Coerce
import Data.Functor.Identity
import Data.Kind (Type)
import Data.Primitive.PrimArray
import Effectful
import Effectful.Dispatch.Static
import Effectful.Dispatch.Static.Primitive
import Effectful.Internal.Env (Env(..))
import Effectful.Internal.Utils
data Provider (e :: Effect) (input :: Type) (f :: Type -> Type) :: Effect
type Provider_ e input = Provider e input Identity
type instance DispatchOf (Provider e input f) = Static NoSideEffects
data instance StaticRep (Provider e input f) where
Provider :: !(Env handlerEs)
-> !(forall r. input -> Eff (e : handlerEs) r -> Eff handlerEs (f r))
-> StaticRep (Provider e input f)
runProvider
:: (forall r. input -> Eff (e : es) r -> Eff es (f r))
-> Eff (Provider e input f : es) a
-> Eff es a
runProvider :: forall input (e :: Effect) (es :: [Effect]) (f :: Type -> Type) a.
(forall r. input -> Eff (e : es) r -> Eff es (f r))
-> Eff (Provider e input f : es) a -> Eff es a
runProvider forall r. input -> Eff (e : es) r -> Eff es (f r)
run Eff (Provider e input f : es) a
m = (Env es -> IO a) -> Eff es a
forall (es :: [Effect]) a. (Env es -> IO a) -> Eff es a
unsafeEff ((Env es -> IO a) -> Eff es a) -> (Env es -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \Env es
es0 -> do
IO (Env (Provider e input f : es))
-> (Env (Provider e input f : es) -> IO ())
-> (Env (Provider e input f : es) -> IO a)
-> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
inlineBracket
(EffectRep (DispatchOf (Provider e input f)) (Provider e input f)
-> Relinker
(EffectRep (DispatchOf (Provider e input f))) (Provider e input f)
-> Env es
-> IO (Env (Provider e input f : es))
forall (e :: Effect) (es :: [Effect]).
EffectRep (DispatchOf e) e
-> Relinker (EffectRep (DispatchOf e)) e
-> Env es
-> IO (Env (e : es))
consEnv (Env es
-> (forall r. input -> Eff (e : es) r -> Eff es (f r))
-> StaticRep (Provider e input f)
forall (handlerEs :: [Effect]) input (e :: Effect)
(f :: Type -> Type).
Env handlerEs
-> (forall r.
input -> Eff (e : handlerEs) r -> Eff handlerEs (f r))
-> StaticRep (Provider e input f)
Provider Env es
es0 input -> Eff (e : es) r -> Eff es (f r)
forall r. input -> Eff (e : es) r -> Eff es (f r)
run) Relinker
(EffectRep (DispatchOf (Provider e input f))) (Provider e input f)
Relinker StaticRep (Provider e input f)
forall (e :: Effect) input (f :: Type -> Type).
Relinker StaticRep (Provider e input f)
relinkProvider Env es
es0)
Env (Provider e input f : es) -> IO ()
forall (e :: Effect) (es :: [Effect]). Env (e : es) -> IO ()
unconsEnv
(\Env (Provider e input f : es)
es -> Eff (Provider e input f : es) a
-> Env (Provider e input f : es) -> IO a
forall (es :: [Effect]) a. Eff es a -> Env es -> IO a
unEff Eff (Provider e input f : es) a
m Env (Provider e input f : es)
es)
runProvider_
:: (forall r. input -> Eff (e : es) r -> Eff es r)
-> Eff (Provider_ e input : es) a
-> Eff es a
runProvider_ :: forall input (e :: Effect) (es :: [Effect]) a.
(forall r. input -> Eff (e : es) r -> Eff es r)
-> Eff (Provider_ e input : es) a -> Eff es a
runProvider_ forall r. input -> Eff (e : es) r -> Eff es r
run = (forall r. input -> Eff (e : es) r -> Eff es (Identity r))
-> Eff (Provider e input Identity : es) a -> Eff es a
forall input (e :: Effect) (es :: [Effect]) (f :: Type -> Type) a.
(forall r. input -> Eff (e : es) r -> Eff es (f r))
-> Eff (Provider e input f : es) a -> Eff es a
runProvider ((forall r. input -> Eff (e : es) r -> Eff es (Identity r))
-> Eff (Provider e input Identity : es) a -> Eff es a)
-> (forall r. input -> Eff (e : es) r -> Eff es (Identity r))
-> Eff (Provider e input Identity : es) a
-> Eff es a
forall a b. (a -> b) -> a -> b
$ \input
input -> Eff es r -> Eff es (Identity r)
forall a b. Coercible a b => a -> b
coerce (Eff es r -> Eff es (Identity r))
-> (Eff (e : es) r -> Eff es r)
-> Eff (e : es) r
-> Eff es (Identity r)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. input -> Eff (e : es) r -> Eff es r
forall r. input -> Eff (e : es) r -> Eff es r
run input
input
provide :: Provider e () f :> es => Eff (e : es) a -> Eff es (f a)
provide :: forall (e :: Effect) (f :: Type -> Type) (es :: [Effect]) a.
(Provider e () f :> es) =>
Eff (e : es) a -> Eff es (f a)
provide = () -> Eff (e : es) a -> Eff es (f a)
forall (e :: Effect) input (f :: Type -> Type) (es :: [Effect]) a.
(Provider e input f :> es) =>
input -> Eff (e : es) a -> Eff es (f a)
provideWith ()
provide_ :: Provider_ e () :> es => Eff (e : es) a -> Eff es a
provide_ :: forall (e :: Effect) (es :: [Effect]) a.
(Provider_ e () :> es) =>
Eff (e : es) a -> Eff es a
provide_ = () -> Eff (e : es) a -> Eff es a
forall (e :: Effect) input (es :: [Effect]) a.
(Provider_ e input :> es) =>
input -> Eff (e : es) a -> Eff es a
provideWith_ ()
provideWith
:: Provider e input f :> es
=> input
-> Eff (e : es) a
-> Eff es (f a)
provideWith :: forall (e :: Effect) input (f :: Type -> Type) (es :: [Effect]) a.
(Provider e input f :> es) =>
input -> Eff (e : es) a -> Eff es (f a)
provideWith input
input Eff (e : es) a
action = (Env es -> IO (f a)) -> Eff es (f a)
forall (es :: [Effect]) a. (Env es -> IO a) -> Eff es a
unsafeEff ((Env es -> IO (f a)) -> Eff es (f a))
-> (Env es -> IO (f a)) -> Eff es (f a)
forall a b. (a -> b) -> a -> b
$ \Env es
es -> do
Provider Env handlerEs
handlerEs forall r. input -> Eff (e : handlerEs) r -> Eff handlerEs (f r)
run <- Env es
-> IO
(EffectRep (DispatchOf (Provider e input f)) (Provider e input f))
forall (e :: Effect) (es :: [Effect]).
(e :> es) =>
Env es -> IO (EffectRep (DispatchOf e) e)
getEnv Env es
es
(Eff handlerEs (f a) -> Env handlerEs -> IO (f a)
forall (es :: [Effect]) a. Eff es a -> Env es -> IO a
`unEff` Env handlerEs
handlerEs) (Eff handlerEs (f a) -> IO (f a))
-> ((Env (e : handlerEs) -> IO a) -> Eff handlerEs (f a))
-> (Env (e : handlerEs) -> IO a)
-> IO (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. input -> Eff (e : handlerEs) a -> Eff handlerEs (f a)
forall r. input -> Eff (e : handlerEs) r -> Eff handlerEs (f r)
run input
input (Eff (e : handlerEs) a -> Eff handlerEs (f a))
-> ((Env (e : handlerEs) -> IO a) -> Eff (e : handlerEs) a)
-> (Env (e : handlerEs) -> IO a)
-> Eff handlerEs (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Env (e : handlerEs) -> IO a) -> Eff (e : handlerEs) a
forall (es :: [Effect]) a. (Env es -> IO a) -> Eff es a
unsafeEff ((Env (e : handlerEs) -> IO a) -> IO (f a))
-> (Env (e : handlerEs) -> IO a) -> IO (f a)
forall a b. (a -> b) -> a -> b
$ \Env (e : handlerEs)
eHandlerEs -> do
Eff (e : es) a -> Env (e : es) -> IO a
forall (es :: [Effect]) a. Eff es a -> Env es -> IO a
unEff Eff (e : es) a
action (Env (e : es) -> IO a) -> IO (Env (e : es)) -> IO a
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Env (e : handlerEs) -> Env es -> IO (Env (e : es))
forall (e :: Effect) (handlerEs :: [Effect]) (es :: [Effect]).
Env (e : handlerEs) -> Env es -> IO (Env (e : es))
copyRef Env (e : handlerEs)
eHandlerEs Env es
es
provideWith_
:: Provider_ e input :> es
=> input
-> Eff (e : es) a
-> Eff es a
provideWith_ :: forall (e :: Effect) input (es :: [Effect]) a.
(Provider_ e input :> es) =>
input -> Eff (e : es) a -> Eff es a
provideWith_ input
input = Eff es (Identity a) -> Eff es a
forall (es :: [Effect]) a. Eff es (Identity a) -> Eff es a
adapt (Eff es (Identity a) -> Eff es a)
-> (Eff (e : es) a -> Eff es (Identity a))
-> Eff (e : es) a
-> Eff es a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. input -> Eff (e : es) a -> Eff es (Identity a)
forall (e :: Effect) input (f :: Type -> Type) (es :: [Effect]) a.
(Provider e input f :> es) =>
input -> Eff (e : es) a -> Eff es (f a)
provideWith input
input
where
adapt :: Eff es (Identity a) -> Eff es a
adapt :: forall (es :: [Effect]) a. Eff es (Identity a) -> Eff es a
adapt = Eff es (Identity a) -> Eff es a
forall a b. Coercible a b => a -> b
coerce
relinkProvider :: Relinker StaticRep (Provider e input f)
relinkProvider :: forall (e :: Effect) input (f :: Type -> Type).
Relinker StaticRep (Provider e input f)
relinkProvider = ((forall (es :: [Effect]). Env es -> IO (Env es))
-> StaticRep (Provider e input f)
-> IO (StaticRep (Provider e input f)))
-> Relinker StaticRep (Provider e input f)
forall (a :: Effect -> Type) (b :: Effect).
((forall (es :: [Effect]). Env es -> IO (Env es))
-> a b -> IO (a b))
-> Relinker a b
Relinker (((forall (es :: [Effect]). Env es -> IO (Env es))
-> StaticRep (Provider e input f)
-> IO (StaticRep (Provider e input f)))
-> Relinker StaticRep (Provider e input f))
-> ((forall (es :: [Effect]). Env es -> IO (Env es))
-> StaticRep (Provider e input f)
-> IO (StaticRep (Provider e input f)))
-> Relinker StaticRep (Provider e input f)
forall a b. (a -> b) -> a -> b
$ \forall (es :: [Effect]). Env es -> IO (Env es)
relink (Provider Env handlerEs
handlerEs forall r. input -> Eff (e : handlerEs) r -> Eff handlerEs (f r)
run) -> do
Env handlerEs
newHandlerEs <- Env handlerEs -> IO (Env handlerEs)
forall (es :: [Effect]). Env es -> IO (Env es)
relink Env handlerEs
handlerEs
StaticRep (Provider e input f)
-> IO (StaticRep (Provider e input f))
forall a. a -> IO a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (StaticRep (Provider e input f)
-> IO (StaticRep (Provider e input f)))
-> StaticRep (Provider e input f)
-> IO (StaticRep (Provider e input f))
forall a b. (a -> b) -> a -> b
$ Env handlerEs
-> (forall r.
input -> Eff (e : handlerEs) r -> Eff handlerEs (f r))
-> StaticRep (Provider e input f)
forall (handlerEs :: [Effect]) input (e :: Effect)
(f :: Type -> Type).
Env handlerEs
-> (forall r.
input -> Eff (e : handlerEs) r -> Eff handlerEs (f r))
-> StaticRep (Provider e input f)
Provider Env handlerEs
newHandlerEs input -> Eff (e : handlerEs) r -> Eff handlerEs (f r)
forall r. input -> Eff (e : handlerEs) r -> Eff handlerEs (f r)
run
copyRef :: Env (e : handlerEs) -> Env es -> IO (Env (e : es))
copyRef :: forall (e :: Effect) (handlerEs :: [Effect]) (es :: [Effect]).
Env (e : handlerEs) -> Env es -> IO (Env (e : es))
copyRef (Env Int
hoffset PrimArray Int
hrefs IORef' Storage
hstorage) (Env Int
offset PrimArray Int
refs0 IORef' Storage
storage) = do
Bool -> IO () -> IO ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
when (IORef' Storage
hstorage IORef' Storage -> IORef' Storage -> Bool
forall a. Eq a => a -> a -> Bool
/= IORef' Storage
storage) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
[Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"storages do not match"
let size :: Int
size = PrimArray Int -> Int
forall a. Prim a => PrimArray a -> Int
sizeofPrimArray PrimArray Int
refs0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
offset
MutablePrimArray RealWorld Int
mrefs <- Int -> IO (MutablePrimArray (PrimState IO) Int)
forall (m :: Type -> Type) a.
(PrimMonad m, Prim a) =>
Int -> m (MutablePrimArray (PrimState m) a)
newPrimArray (Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
MutablePrimArray (PrimState IO) Int
-> Int -> PrimArray Int -> Int -> Int -> IO ()
forall (m :: Type -> Type) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a
-> Int -> PrimArray a -> Int -> Int -> m ()
copyPrimArray MutablePrimArray RealWorld Int
MutablePrimArray (PrimState IO) Int
mrefs Int
0 PrimArray Int
hrefs Int
hoffset Int
2
MutablePrimArray (PrimState IO) Int
-> Int -> PrimArray Int -> Int -> Int -> IO ()
forall (m :: Type -> Type) a.
(PrimMonad m, Prim a) =>
MutablePrimArray (PrimState m) a
-> Int -> PrimArray a -> Int -> Int -> m ()
copyPrimArray MutablePrimArray RealWorld Int
MutablePrimArray (PrimState IO) Int
mrefs Int
2 PrimArray Int
refs0 Int
offset Int
size
PrimArray Int
refs <- MutablePrimArray (PrimState IO) Int -> IO (PrimArray Int)
forall (m :: Type -> Type) a.
PrimMonad m =>
MutablePrimArray (PrimState m) a -> m (PrimArray a)
unsafeFreezePrimArray MutablePrimArray RealWorld Int
MutablePrimArray (PrimState IO) Int
mrefs
Env (e : es) -> IO (Env (e : es))
forall a. a -> IO a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Env (e : es) -> IO (Env (e : es)))
-> Env (e : es) -> IO (Env (e : es))
forall a b. (a -> b) -> a -> b
$ Int -> PrimArray Int -> IORef' Storage -> Env (e : es)
forall (es :: [Effect]).
Int -> PrimArray Int -> IORef' Storage -> Env es
Env Int
0 PrimArray Int
refs IORef' Storage
storage