{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, RankNTypes, TypeOperators, UndecidableInstances #-}
module Control.Carrier.State.IORef
(
runState
, evalState
, execState
, StateC(..)
, module Control.Effect.State
) where
import Control.Applicative (Alternative (..))
import Control.Algebra
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
runState :: MonadIO m => s -> StateC s m a -> m (s, a)
runState s x = do
ref <- liftIO $ newIORef s
result <- runReader ref . runStateC $ x
final <- liftIO . readIORef $ ref
pure (final, result)
{-# INLINE[3] runState #-}
evalState :: forall s m a . MonadIO m => s -> StateC s m a -> m a
evalState s x = do
ref <- liftIO $ newIORef s
runReader ref . runStateC $ x
{-# INLINE[3] evalState #-}
execState :: forall s m a . MonadIO m => s -> StateC s m a -> m s
execState s = fmap fst . runState s
{-# INLINE[3] execState #-}
newtype StateC s m a = StateC { runStateC :: ReaderC (IORef s) m a }
deriving (Alternative, Applicative, Functor, Monad, Fail.MonadFail, MonadFix, MonadIO, MonadPlus)
instance (MonadIO m, Algebra sig m, Effect sig) => Algebra (State s :+: sig) (StateC s m) where
alg (L act) = do
ref <- StateC ask
case act of
Put s k -> liftIO (writeIORef ref s) *> k
Get k -> liftIO (readIORef ref) >>= k
alg (R other) = StateC (alg (R (handleCoercible other)))
{-# INLINE alg #-}