-- | Support for access to a read only value of a particular type.
module Effectful.Reader.Static
  ( -- * Effect
    Reader

    -- ** Handlers
  , runReader
  , withReader

    -- ** Operations
  , ask
  , asks
  , local
  ) where

import Effectful
import Effectful.Dispatch.Static

-- | Provide access to a strict (WHNF), thread local, read only value of type
-- @r@.
data Reader r :: Effect

type instance DispatchOf (Reader r) = Static NoSideEffects
newtype instance StaticRep (Reader r) = Reader r

-- | Run a 'Reader' effect with the given initial environment.
runReader
  :: r -- ^ The initial environment.
  -> Eff (Reader r : es) a
  -> Eff es a
runReader :: r -> Eff (Reader r : es) a -> Eff es a
runReader r
r = StaticRep (Reader r) -> Eff (Reader r : es) a -> Eff es a
forall (e :: (Type -> Type) -> Type -> Type)
       (sideEffects :: SideEffects)
       (es :: [(Type -> Type) -> Type -> Type]) a.
(DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) =>
StaticRep e -> Eff (e : es) a -> Eff es a
evalStaticRep (r -> StaticRep (Reader r)
forall r. r -> StaticRep (Reader r)
Reader r
r)

-- | Execute a computation in a modified environment.
--
-- @since 1.1.0.0
withReader
  :: (r1 -> r2)
  -- ^ The function to modify the environment.
  -> Eff (Reader r2 : es) a
  -- ^ Computation to run in the modified environment.
  -> Eff (Reader r1 : es) a
withReader :: (r1 -> r2) -> Eff (Reader r2 : es) a -> Eff (Reader r1 : es) a
withReader r1 -> r2
f Eff (Reader r2 : es) a
m = do
  r1
r <- Eff (Reader r1 : es) r1
forall r (es :: [(Type -> Type) -> Type -> Type]).
(Reader r :> es) =>
Eff es r
ask
  Eff es a -> Eff (Reader r1 : es) a
forall (es :: [(Type -> Type) -> Type -> Type]) a
       (e :: (Type -> Type) -> Type -> Type).
Eff es a -> Eff (e : es) a
raise (Eff es a -> Eff (Reader r1 : es) a)
-> Eff es a -> Eff (Reader r1 : es) a
forall a b. (a -> b) -> a -> b
$ r2 -> Eff (Reader r2 : es) a -> Eff es a
forall r (es :: [(Type -> Type) -> Type -> Type]) a.
r -> Eff (Reader r : es) a -> Eff es a
runReader (r1 -> r2
f r1
r) Eff (Reader r2 : es) a
m

-- | Fetch the value of the environment.
ask :: Reader r :> es => Eff es r
ask :: Eff es r
ask = do
  Reader r <- Eff es (StaticRep (Reader r))
forall (e :: (Type -> Type) -> Type -> Type)
       (sideEffects :: SideEffects)
       (es :: [(Type -> Type) -> Type -> Type]).
(DispatchOf e ~ 'Static sideEffects, e :> es) =>
Eff es (StaticRep e)
getStaticRep
  r -> Eff es r
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure r
r

-- | Retrieve a function of the current environment.
--
-- @'asks' f ≡ f '<$>' 'ask'@
asks
  :: Reader r :> es
  => (r -> a) -- ^ The function to apply to the environment.
  -> Eff es a
asks :: (r -> a) -> Eff es a
asks r -> a
f = r -> a
f (r -> a) -> Eff es r -> Eff es a
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Eff es r
forall r (es :: [(Type -> Type) -> Type -> Type]).
(Reader r :> es) =>
Eff es r
ask

-- | Execute a computation in a modified environment.
--
-- @'runReader' r ('local' f m) ≡ 'runReader' (f r) m@
--
local
  :: Reader r :> es
  => (r -> r) -- ^ The function to modify the environment.
  -> Eff es a
  -> Eff es a
local :: (r -> r) -> Eff es a -> Eff es a
local r -> r
f = (StaticRep (Reader r) -> StaticRep (Reader r))
-> Eff es a -> Eff es a
forall (e :: (Type -> Type) -> Type -> Type)
       (sideEffects :: SideEffects)
       (es :: [(Type -> Type) -> Type -> Type]) a.
(DispatchOf e ~ 'Static sideEffects, e :> es) =>
(StaticRep e -> StaticRep e) -> Eff es a -> Eff es a
localStaticRep ((StaticRep (Reader r) -> StaticRep (Reader r))
 -> Eff es a -> Eff es a)
-> (StaticRep (Reader r) -> StaticRep (Reader r))
-> Eff es a
-> Eff es a
forall a b. (a -> b) -> a -> b
$ \(Reader r) -> r -> StaticRep (Reader r)
forall r. r -> StaticRep (Reader r)
Reader (r -> r
f r
r)