{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

{- | A carrier for the 'State' effect. It uses an 'IORef' internally to handle its state, and thus is safe to use with "Control.Carrier.Resource". Underlying 'IORef' operations are performed with 'readIORef' and 'writeIORef'.

Note that the parameter order in 'runState', 'evalState', and 'execState' is reversed compared the equivalent functions provided by @transformers@. This is an intentional decision made to enable the composition of effect handlers with '.' without invoking 'flip'.
-}
module Control.Carrier.State.IORef
( -- * Strict state carrier
  runState
, evalState
, execState
, StateC(..)
-- * State effect
, module Control.Effect.State
) where

import           Control.Algebra
import           Control.Applicative (Alternative(..))
import           Control.Carrier.Reader
import           Control.Effect.State
import           Control.Monad (MonadPlus(..))
import qualified Control.Monad.Fail as Fail
import           Control.Monad.Fix
import           Control.Monad.IO.Class
import           Control.Monad.Trans.Class
import           Data.IORef

-- | Run a 'State' effect starting from the passed value.
--
--   prop> run (runState a (pure b)) === (a, b)
--
-- @since 1.0.0.0
runState :: MonadIO m => s -> StateC s m a -> m (s, a)
runState :: s -> StateC s m a -> m (s, a)
runState s
s StateC s m a
x = do
  IORef s
ref <- IO (IORef s) -> m (IORef s)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef s) -> m (IORef s)) -> IO (IORef s) -> m (IORef s)
forall a b. (a -> b) -> a -> b
$ s -> IO (IORef s)
forall a. a -> IO (IORef a)
newIORef s
s
  a
result <- IORef s -> ReaderC (IORef s) m a -> m a
forall r (m :: * -> *) a. r -> ReaderC r m a -> m a
runReader IORef s
ref (ReaderC (IORef s) m a -> m a)
-> (StateC s m a -> ReaderC (IORef s) m a) -> StateC s m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateC s m a -> ReaderC (IORef s) m a
forall s (m :: * -> *) a. StateC s m a -> ReaderC (IORef s) m a
runStateC (StateC s m a -> m a) -> StateC s m a -> m a
forall a b. (a -> b) -> a -> b
$ StateC s m a
x
  s
final <- IO s -> m s
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO s -> m s) -> (IORef s -> IO s) -> IORef s -> m s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IORef s -> IO s
forall a. IORef a -> IO a
readIORef (IORef s -> m s) -> IORef s -> m s
forall a b. (a -> b) -> a -> b
$ IORef s
ref
  (s, a) -> m (s, a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (s
final, a
result)
{-# INLINE[3] runState #-}

-- | Run a 'State' effect, yielding the result value and discarding the final state.
--
--   prop> run (evalState a (pure b)) === b
--
-- @since 1.0.0.0
evalState :: forall s m a . MonadIO m => s -> StateC s m a -> m a
evalState :: s -> StateC s m a -> m a
evalState s
s StateC s m a
x = do
  IORef s
ref <- IO (IORef s) -> m (IORef s)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IORef s) -> m (IORef s)) -> IO (IORef s) -> m (IORef s)
forall a b. (a -> b) -> a -> b
$ s -> IO (IORef s)
forall a. a -> IO (IORef a)
newIORef s
s
  IORef s -> ReaderC (IORef s) m a -> m a
forall r (m :: * -> *) a. r -> ReaderC r m a -> m a
runReader IORef s
ref (ReaderC (IORef s) m a -> m a)
-> (StateC s m a -> ReaderC (IORef s) m a) -> StateC s m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateC s m a -> ReaderC (IORef s) m a
forall s (m :: * -> *) a. StateC s m a -> ReaderC (IORef s) m a
runStateC (StateC s m a -> m a) -> StateC s m a -> m a
forall a b. (a -> b) -> a -> b
$ StateC s m a
x
{-# INLINE[3] evalState #-}

-- | Run a 'State' effect, yielding the final state and discarding the return value.
--
--   prop> run (execState a (pure b)) === a
--
-- @since 1.0.0.0
execState :: forall s m a . MonadIO m => s -> StateC s m a -> m s
execState :: s -> StateC s m a -> m s
execState s
s = ((s, a) -> s) -> m (s, a) -> m s
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (s, a) -> s
forall a b. (a, b) -> a
fst (m (s, a) -> m s)
-> (StateC s m a -> m (s, a)) -> StateC s m a -> m s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> StateC s m a -> m (s, a)
forall (m :: * -> *) s a.
MonadIO m =>
s -> StateC s m a -> m (s, a)
runState s
s
{-# INLINE[3] execState #-}

-- | @since 1.0.0.0
newtype StateC s m a = StateC { StateC s m a -> ReaderC (IORef s) m a
runStateC :: ReaderC (IORef s) m a }
  deriving (Applicative (StateC s m)
StateC s m a
Applicative (StateC s m)
-> (forall a. StateC s m a)
-> (forall a. StateC s m a -> StateC s m a -> StateC s m a)
-> (forall a. StateC s m a -> StateC s m [a])
-> (forall a. StateC s m a -> StateC s m [a])
-> Alternative (StateC s m)
StateC s m a -> StateC s m a -> StateC s m a
StateC s m a -> StateC s m [a]
StateC s m a -> StateC s m [a]
forall a. StateC s m a
forall a. StateC s m a -> StateC s m [a]
forall a. StateC s m a -> StateC s m a -> StateC s m a
forall s (m :: * -> *). Alternative m => Applicative (StateC s m)
forall s (m :: * -> *) a. Alternative m => StateC s m a
forall s (m :: * -> *) a.
Alternative m =>
StateC s m a -> StateC s m [a]
forall s (m :: * -> *) a.
Alternative m =>
StateC s m a -> StateC s m a -> StateC s m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: StateC s m a -> StateC s m [a]
$cmany :: forall s (m :: * -> *) a.
Alternative m =>
StateC s m a -> StateC s m [a]
some :: StateC s m a -> StateC s m [a]
$csome :: forall s (m :: * -> *) a.
Alternative m =>
StateC s m a -> StateC s m [a]
<|> :: StateC s m a -> StateC s m a -> StateC s m a
$c<|> :: forall s (m :: * -> *) a.
Alternative m =>
StateC s m a -> StateC s m a -> StateC s m a
empty :: StateC s m a
$cempty :: forall s (m :: * -> *) a. Alternative m => StateC s m a
$cp1Alternative :: forall s (m :: * -> *). Alternative m => Applicative (StateC s m)
Alternative, Functor (StateC s m)
a -> StateC s m a
Functor (StateC s m)
-> (forall a. a -> StateC s m a)
-> (forall a b.
    StateC s m (a -> b) -> StateC s m a -> StateC s m b)
-> (forall a b c.
    (a -> b -> c) -> StateC s m a -> StateC s m b -> StateC s m c)
-> (forall a b. StateC s m a -> StateC s m b -> StateC s m b)
-> (forall a b. StateC s m a -> StateC s m b -> StateC s m a)
-> Applicative (StateC s m)
StateC s m a -> StateC s m b -> StateC s m b
StateC s m a -> StateC s m b -> StateC s m a
StateC s m (a -> b) -> StateC s m a -> StateC s m b
(a -> b -> c) -> StateC s m a -> StateC s m b -> StateC s m c
forall a. a -> StateC s m a
forall a b. StateC s m a -> StateC s m b -> StateC s m a
forall a b. StateC s m a -> StateC s m b -> StateC s m b
forall a b. StateC s m (a -> b) -> StateC s m a -> StateC s m b
forall a b c.
(a -> b -> c) -> StateC s m a -> StateC s m b -> StateC s m c
forall s (m :: * -> *). Applicative m => Functor (StateC s m)
forall s (m :: * -> *) a. Applicative m => a -> StateC s m a
forall s (m :: * -> *) a b.
Applicative m =>
StateC s m a -> StateC s m b -> StateC s m a
forall s (m :: * -> *) a b.
Applicative m =>
StateC s m a -> StateC s m b -> StateC s m b
forall s (m :: * -> *) a b.
Applicative m =>
StateC s m (a -> b) -> StateC s m a -> StateC s m b
forall s (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> StateC s m a -> StateC s m b -> StateC s 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
<* :: StateC s m a -> StateC s m b -> StateC s m a
$c<* :: forall s (m :: * -> *) a b.
Applicative m =>
StateC s m a -> StateC s m b -> StateC s m a
*> :: StateC s m a -> StateC s m b -> StateC s m b
$c*> :: forall s (m :: * -> *) a b.
Applicative m =>
StateC s m a -> StateC s m b -> StateC s m b
liftA2 :: (a -> b -> c) -> StateC s m a -> StateC s m b -> StateC s m c
$cliftA2 :: forall s (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> StateC s m a -> StateC s m b -> StateC s m c
<*> :: StateC s m (a -> b) -> StateC s m a -> StateC s m b
$c<*> :: forall s (m :: * -> *) a b.
Applicative m =>
StateC s m (a -> b) -> StateC s m a -> StateC s m b
pure :: a -> StateC s m a
$cpure :: forall s (m :: * -> *) a. Applicative m => a -> StateC s m a
$cp1Applicative :: forall s (m :: * -> *). Applicative m => Functor (StateC s m)
Applicative, a -> StateC s m b -> StateC s m a
(a -> b) -> StateC s m a -> StateC s m b
(forall a b. (a -> b) -> StateC s m a -> StateC s m b)
-> (forall a b. a -> StateC s m b -> StateC s m a)
-> Functor (StateC s m)
forall a b. a -> StateC s m b -> StateC s m a
forall a b. (a -> b) -> StateC s m a -> StateC s m b
forall s (m :: * -> *) a b.
Functor m =>
a -> StateC s m b -> StateC s m a
forall s (m :: * -> *) a b.
Functor m =>
(a -> b) -> StateC s m a -> StateC s m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> StateC s m b -> StateC s m a
$c<$ :: forall s (m :: * -> *) a b.
Functor m =>
a -> StateC s m b -> StateC s m a
fmap :: (a -> b) -> StateC s m a -> StateC s m b
$cfmap :: forall s (m :: * -> *) a b.
Functor m =>
(a -> b) -> StateC s m a -> StateC s m b
Functor, Applicative (StateC s m)
a -> StateC s m a
Applicative (StateC s m)
-> (forall a b.
    StateC s m a -> (a -> StateC s m b) -> StateC s m b)
-> (forall a b. StateC s m a -> StateC s m b -> StateC s m b)
-> (forall a. a -> StateC s m a)
-> Monad (StateC s m)
StateC s m a -> (a -> StateC s m b) -> StateC s m b
StateC s m a -> StateC s m b -> StateC s m b
forall a. a -> StateC s m a
forall a b. StateC s m a -> StateC s m b -> StateC s m b
forall a b. StateC s m a -> (a -> StateC s m b) -> StateC s m b
forall s (m :: * -> *). Monad m => Applicative (StateC s m)
forall s (m :: * -> *) a. Monad m => a -> StateC s m a
forall s (m :: * -> *) a b.
Monad m =>
StateC s m a -> StateC s m b -> StateC s m b
forall s (m :: * -> *) a b.
Monad m =>
StateC s m a -> (a -> StateC s m b) -> StateC s 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 -> StateC s m a
$creturn :: forall s (m :: * -> *) a. Monad m => a -> StateC s m a
>> :: StateC s m a -> StateC s m b -> StateC s m b
$c>> :: forall s (m :: * -> *) a b.
Monad m =>
StateC s m a -> StateC s m b -> StateC s m b
>>= :: StateC s m a -> (a -> StateC s m b) -> StateC s m b
$c>>= :: forall s (m :: * -> *) a b.
Monad m =>
StateC s m a -> (a -> StateC s m b) -> StateC s m b
$cp1Monad :: forall s (m :: * -> *). Monad m => Applicative (StateC s m)
Monad, Monad (StateC s m)
Monad (StateC s m)
-> (forall a. String -> StateC s m a) -> MonadFail (StateC s m)
String -> StateC s m a
forall a. String -> StateC s m a
forall s (m :: * -> *). MonadFail m => Monad (StateC s m)
forall s (m :: * -> *) a. MonadFail m => String -> StateC s m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> StateC s m a
$cfail :: forall s (m :: * -> *) a. MonadFail m => String -> StateC s m a
$cp1MonadFail :: forall s (m :: * -> *). MonadFail m => Monad (StateC s m)
Fail.MonadFail, Monad (StateC s m)
Monad (StateC s m)
-> (forall a. (a -> StateC s m a) -> StateC s m a)
-> MonadFix (StateC s m)
(a -> StateC s m a) -> StateC s m a
forall a. (a -> StateC s m a) -> StateC s m a
forall s (m :: * -> *). MonadFix m => Monad (StateC s m)
forall s (m :: * -> *) a.
MonadFix m =>
(a -> StateC s m a) -> StateC s m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> StateC s m a) -> StateC s m a
$cmfix :: forall s (m :: * -> *) a.
MonadFix m =>
(a -> StateC s m a) -> StateC s m a
$cp1MonadFix :: forall s (m :: * -> *). MonadFix m => Monad (StateC s m)
MonadFix, Monad (StateC s m)
Monad (StateC s m)
-> (forall a. IO a -> StateC s m a) -> MonadIO (StateC s m)
IO a -> StateC s m a
forall a. IO a -> StateC s m a
forall s (m :: * -> *). MonadIO m => Monad (StateC s m)
forall s (m :: * -> *) a. MonadIO m => IO a -> StateC s m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> StateC s m a
$cliftIO :: forall s (m :: * -> *) a. MonadIO m => IO a -> StateC s m a
$cp1MonadIO :: forall s (m :: * -> *). MonadIO m => Monad (StateC s m)
MonadIO, Monad (StateC s m)
Alternative (StateC s m)
StateC s m a
Alternative (StateC s m)
-> Monad (StateC s m)
-> (forall a. StateC s m a)
-> (forall a. StateC s m a -> StateC s m a -> StateC s m a)
-> MonadPlus (StateC s m)
StateC s m a -> StateC s m a -> StateC s m a
forall a. StateC s m a
forall a. StateC s m a -> StateC s m a -> StateC s m a
forall s (m :: * -> *).
(Alternative m, Monad m) =>
Monad (StateC s m)
forall s (m :: * -> *).
(Alternative m, Monad m) =>
Alternative (StateC s m)
forall s (m :: * -> *) a. (Alternative m, Monad m) => StateC s m a
forall s (m :: * -> *) a.
(Alternative m, Monad m) =>
StateC s m a -> StateC s m a -> StateC s m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: StateC s m a -> StateC s m a -> StateC s m a
$cmplus :: forall s (m :: * -> *) a.
(Alternative m, Monad m) =>
StateC s m a -> StateC s m a -> StateC s m a
mzero :: StateC s m a
$cmzero :: forall s (m :: * -> *) a. (Alternative m, Monad m) => StateC s m a
$cp2MonadPlus :: forall s (m :: * -> *).
(Alternative m, Monad m) =>
Monad (StateC s m)
$cp1MonadPlus :: forall s (m :: * -> *).
(Alternative m, Monad m) =>
Alternative (StateC s m)
MonadPlus)

instance (MonadIO m, Algebra sig m) => Algebra (State s :+: sig) (StateC s m) where
  alg :: Handler ctx n (StateC s m)
-> (:+:) (State s) sig n a -> ctx () -> StateC s m (ctx a)
alg Handler ctx n (StateC s m)
hdl (:+:) (State s) sig n a
sig ctx ()
ctx = case (:+:) (State s) sig n a
sig of
    L State s n a
act -> do
      IORef s
ref <- ReaderC (IORef s) m (IORef s) -> StateC s m (IORef s)
forall s (m :: * -> *) a. ReaderC (IORef s) m a -> StateC s m a
StateC (forall r (sig :: (* -> *) -> * -> *) (m :: * -> *).
Has (Reader r) sig m =>
m r
forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
Has (Reader (IORef s)) sig m =>
m (IORef s)
ask @(IORef s))
      (a -> ctx () -> ctx a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ctx ()
ctx) (a -> ctx a) -> StateC s m a -> StateC s m (ctx a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case State s n a
act of
        Put s
s -> IO () -> StateC s m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IORef s -> s -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef s
ref s
s)
        State s n a
Get   -> IO s -> StateC s m s
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IORef s -> IO s
forall a. IORef a -> IO a
readIORef IORef s
ref)
    R sig n a
other -> ReaderC (IORef s) m (ctx a) -> StateC s m (ctx a)
forall s (m :: * -> *) a. ReaderC (IORef s) m a -> StateC s m a
StateC (Handler ctx n (ReaderC (IORef s) m)
-> (:+:) (Reader (IORef s)) sig n a
-> ctx ()
-> ReaderC (IORef s) m (ctx a)
forall (sig :: (* -> *) -> * -> *) (m :: * -> *) (ctx :: * -> *)
       (n :: * -> *) a.
(Algebra sig m, Functor ctx) =>
Handler ctx n m -> sig n a -> ctx () -> m (ctx a)
alg (StateC s m (ctx x) -> ReaderC (IORef s) m (ctx x)
forall s (m :: * -> *) a. StateC s m a -> ReaderC (IORef s) m a
runStateC (StateC s m (ctx x) -> ReaderC (IORef s) m (ctx x))
-> (ctx (n x) -> StateC s m (ctx x))
-> ctx (n x)
-> ReaderC (IORef s) m (ctx x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ctx (n x) -> StateC s m (ctx x)
Handler ctx n (StateC s m)
hdl) (sig n a -> (:+:) (Reader (IORef s)) sig n a
forall (f :: (* -> *) -> * -> *) (g :: (* -> *) -> * -> *)
       (m :: * -> *) k.
g m k -> (:+:) f g m k
R sig n a
other) ctx ()
ctx)
  {-# INLINE alg #-}