{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DeriveDataTypeable #-}
module LiveCoding.Cell.Monad.Trans where
import Control.Arrow (arr, (>>>))
import Data.Data (Data)
import Control.Monad.Trans.Reader (runReaderT, ReaderT)
import Control.Monad.Trans.State.Strict (StateT (..), runStateT, evalStateT)
import LiveCoding.Cell
import LiveCoding.Cell.Monad
runStateC
:: (Data stateT, Monad m)
=> Cell (StateT stateT m) a b
-> stateT
-> Cell m a (b, stateT)
runStateC cell stateT = hoistCellKleisliStateChange morph init cell
where
morph step State { .. } a = do
((b, stateInternal), stateT) <- runStateT (step stateInternal a) stateT
return ((b, stateT), State { .. })
init stateInternal = State { .. }
runStateC_
:: (Data stateT, Monad m)
=> Cell (StateT stateT m) a b
-> stateT
-> Cell m a b
runStateC_ cell stateT = runStateC cell stateT >>> arr fst
data State stateT stateInternal = State
{ stateT :: stateT
, stateInternal :: stateInternal
}
deriving (Data, Eq, Show)
runReaderC
:: r
-> Cell (ReaderT r m) a b
-> Cell m a b
runReaderC r = hoistCell $ flip runReaderT r
runReaderC'
:: Monad m
=> Cell (ReaderT r m) a b
-> Cell m (r, a) b
runReaderC' = hoistCellKleisli_ $ \action (r, a) -> runReaderT (action a) r