-- | The dynamically dispatched variant of the 'State' effect.
--
-- /Note:/ unless you plan to change interpretations at runtime, it's
-- recommended to use one of the statically dispatched variants,
-- i.e. "Effectful.State.Static.Local" or "Effectful.State.Static.Shared".
module Effectful.State.Dynamic
  ( -- * Effect
    State(..)

    -- ** Handlers

    -- *** Local
  , runStateLocal
  , evalStateLocal
  , execStateLocal

    -- *** Shared
  , runStateShared
  , evalStateShared
  , execStateShared

    -- ** Operations
  , get
  , gets
  , put
  , state
  , modify
  , stateM
  , modifyM
  ) where

import Effectful
import Effectful.Dispatch.Dynamic
import qualified Effectful.State.Static.Local as L
import qualified Effectful.State.Static.Shared as S

-- | Provide access to a mutable value of type @s@.
data State s :: Effect where
  Get    :: State s m s
  Put    :: s -> State s m ()
  State  :: (s ->   (a, s)) -> State s m a
  StateM :: (s -> m (a, s)) -> State s m a

type instance DispatchOf (State s) = Dynamic

----------------------------------------
-- Local

-- | Run the 'State' effect with the given initial state and return the final
-- value along with the final state (via "Effectful.State.Static.Local").
runStateLocal :: s -> Eff (State s : es) a -> Eff es (a, s)
runStateLocal :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es (a, s)
runStateLocal s
s0 = forall (e :: (Type -> Type) -> Type -> Type)
       (handlerEs :: [(Type -> Type) -> Type -> Type]) a
       (es :: [(Type -> Type) -> Type -> Type]) b.
(DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret (forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es (a, s)
L.runState s
s0) forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
localState

-- | Run the 'State' effect with the given initial state and return the final
-- value, discarding the final state (via "Effectful.State.Static.Local").
evalStateLocal :: s -> Eff (State s : es) a -> Eff es a
evalStateLocal :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es a
evalStateLocal s
s0 = forall (e :: (Type -> Type) -> Type -> Type)
       (handlerEs :: [(Type -> Type) -> Type -> Type]) a
       (es :: [(Type -> Type) -> Type -> Type]) b.
(DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret (forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es a
L.evalState s
s0) forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
localState

-- | Run the 'State' effect with the given initial state and return the final
-- state, discarding the final value (via "Effectful.State.Static.Local").
execStateLocal :: s -> Eff (State s : es) a -> Eff es s
execStateLocal :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es s
execStateLocal s
s0 = forall (e :: (Type -> Type) -> Type -> Type)
       (handlerEs :: [(Type -> Type) -> Type -> Type]) a
       (es :: [(Type -> Type) -> Type -> Type]) b.
(DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret (forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es s
L.execState s
s0) forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
localState

localState
  :: L.State s :> es
  => LocalEnv localEs es
  -> State s (Eff localEs) a
  -> Eff es a
localState :: forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
localState LocalEnv localEs es
env = \case
  State s (Eff localEs) a
Get      -> forall s (es :: [(Type -> Type) -> Type -> Type]).
(State s :> es) =>
Eff es s
L.get
  Put s
s    -> forall s (es :: [(Type -> Type) -> Type -> Type]).
(State s :> es) =>
s -> Eff es ()
L.put s
s
  State s -> (a, s)
f  -> forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
(s -> (a, s)) -> Eff es a
L.state s -> (a, s)
f
  StateM s -> Eff localEs (a, s)
f -> 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 es
env forall a b. (a -> b) -> a -> b
$ \forall r. Eff localEs r -> Eff es r
unlift -> forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
(s -> Eff es (a, s)) -> Eff es a
L.stateM (forall r. Eff localEs r -> Eff es r
unlift forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> Eff localEs (a, s)
f)

----------------------------------------
-- Shared

-- | Run the 'State' effect with the given initial state and return the final
-- value along with the final state (via "Effectful.State.Static.Shared").
runStateShared :: s -> Eff (State s : es) a -> Eff es (a, s)
runStateShared :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es (a, s)
runStateShared s
s0 = forall (e :: (Type -> Type) -> Type -> Type)
       (handlerEs :: [(Type -> Type) -> Type -> Type]) a
       (es :: [(Type -> Type) -> Type -> Type]) b.
(DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret (forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es (a, s)
S.runState s
s0) forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
sharedState

-- | Run the 'State' effect with the given initial state and return the final
-- value, discarding the final state (via "Effectful.State.Static.Shared").
evalStateShared :: s -> Eff (State s : es) a -> Eff es a
evalStateShared :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es a
evalStateShared s
s0 = forall (e :: (Type -> Type) -> Type -> Type)
       (handlerEs :: [(Type -> Type) -> Type -> Type]) a
       (es :: [(Type -> Type) -> Type -> Type]) b.
(DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret (forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es a
S.evalState s
s0) forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
sharedState

-- | Run the 'State' effect with the given initial state and return the final
-- state, discarding the final value (via "Effectful.State.Static.Shared").
execStateShared :: s -> Eff (State s : es) a -> Eff es s
execStateShared :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es s
execStateShared s
s0 = forall (e :: (Type -> Type) -> Type -> Type)
       (handlerEs :: [(Type -> Type) -> Type -> Type]) a
       (es :: [(Type -> Type) -> Type -> Type]) b.
(DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret (forall s (es :: [(Type -> Type) -> Type -> Type]) a.
s -> Eff (State s : es) a -> Eff es s
S.execState s
s0) forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
sharedState

sharedState
  :: S.State s :> es
  => LocalEnv localEs es
  -> State s (Eff localEs) a
  -> Eff es a
sharedState :: forall s (es :: [(Type -> Type) -> Type -> Type])
       (localEs :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
LocalEnv localEs es -> State s (Eff localEs) a -> Eff es a
sharedState LocalEnv localEs es
env = \case
  State s (Eff localEs) a
Get      -> forall s (es :: [(Type -> Type) -> Type -> Type]).
(State s :> es) =>
Eff es s
S.get
  Put s
s    -> forall s (es :: [(Type -> Type) -> Type -> Type]).
(State s :> es) =>
s -> Eff es ()
S.put s
s
  State s -> (a, s)
f  -> forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
(s -> (a, s)) -> Eff es a
S.state s -> (a, s)
f
  StateM s -> Eff localEs (a, s)
f -> 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 es
env forall a b. (a -> b) -> a -> b
$ \forall r. Eff localEs r -> Eff es r
unlift -> forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(State s :> es) =>
(s -> Eff es (a, s)) -> Eff es a
S.stateM (forall r. Eff localEs r -> Eff es r
unlift forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> Eff localEs (a, s)
f)

----------------------------------------
-- Operations

-- | Fetch the current value of the state.
get
  :: (HasCallStack, State s :> es)
  => Eff es s
get :: forall s (es :: [(Type -> Type) -> Type -> Type]).
(HasCallStack, State s :> es) =>
Eff es s
get = 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 forall s (m :: Type -> Type). State s m s
Get

-- | Get a function of the current state.
--
-- @'gets' f ≡ f '<$>' 'get'@
gets
  :: (HasCallStack, State s :> es)
  => (s -> a)
  -> Eff es a
gets :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, State s :> es) =>
(s -> a) -> Eff es a
gets s -> a
f = s -> a
f forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (es :: [(Type -> Type) -> Type -> Type]).
(HasCallStack, State s :> es) =>
Eff es s
get

-- | Set the current state to the given value.
put
  :: (HasCallStack, State s :> es)
  => s
  -> Eff es ()
put :: forall s (es :: [(Type -> Type) -> Type -> Type]).
(HasCallStack, State s :> es) =>
s -> Eff es ()
put = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: Type -> Type). s -> State s m ()
Put

-- | Apply the function to the current state and return a value.
state
  :: (HasCallStack, State s :> es)
  => (s -> (a, s))
  -> Eff es a
state :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, State s :> es) =>
(s -> (a, s)) -> Eff es a
state = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a (m :: Type -> Type). (s -> (a, s)) -> State s m a
State

-- | Apply the function to the current state.
--
-- @'modify' f ≡ 'state' (\\s -> ((), f s))@
modify
  :: (HasCallStack, State s :> es)
  => (s -> s)
  -> Eff es ()
modify :: forall s (es :: [(Type -> Type) -> Type -> Type]).
(HasCallStack, State s :> es) =>
(s -> s) -> Eff es ()
modify s -> s
f = forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, State s :> es) =>
(s -> (a, s)) -> Eff es a
state (\s
s -> ((), s -> s
f s
s))

-- | Apply the monadic function to the current state and return a value.
stateM
  :: (HasCallStack, State s :> es)
  => (s -> Eff es (a, s))
  -> Eff es a
stateM :: forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, State s :> es) =>
(s -> Eff es (a, s)) -> Eff es a
stateM = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: Type -> Type) a. (s -> m (a, s)) -> State s m a
StateM

-- | Apply the monadic function to the current state.
--
-- @'modifyM' f ≡ 'stateM' (\\s -> ((), ) '<$>' f s)@
modifyM
  :: (HasCallStack, State s :> es)
  => (s -> Eff es s)
  -> Eff es ()
modifyM :: forall s (es :: [(Type -> Type) -> Type -> Type]).
(HasCallStack, State s :> es) =>
(s -> Eff es s) -> Eff es ()
modifyM s -> Eff es s
f = forall s (es :: [(Type -> Type) -> Type -> Type]) a.
(HasCallStack, State s :> es) =>
(s -> Eff es (a, s)) -> Eff es a
stateM (\s
s -> ((), ) forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> Eff es s
f s
s)