module Data.Ruby.Marshal.Monad where
import Control.Applicative
import Prelude
import Control.Monad.State.Strict (get, gets, lift, put, MonadState, StateT)
import Data.Ruby.Marshal.RubyObject (RubyObject(..))
import Data.Serialize.Get (Get)
import Data.Vector (Vector)
import qualified Data.Vector as V
newtype Marshal a = Marshal {
runMarshal :: StateT Cache Get a
} deriving (Functor, Applicative, Monad, MonadState Cache)
liftMarshal :: Get a -> Marshal a
liftMarshal = Marshal . lift
data Cache = Cache {
objects :: !(Vector RubyObject)
, symbols :: !(Vector RubyObject)
} deriving Show
emptyCache :: Cache
emptyCache = Cache { symbols = V.empty, objects = V.empty }
readCache :: Int -> (Cache -> Vector RubyObject) -> Marshal (Maybe RubyObject)
readCache index f = gets f >>= \cache -> return $ cache V.!? index
readObject :: Int -> Marshal (Maybe RubyObject)
readObject index = readCache index objects
readSymbol :: Int -> Marshal (Maybe RubyObject)
readSymbol index = readCache index symbols
writeCache :: RubyObject -> Marshal ()
writeCache object = do
cache <- get
case object of
RIVar _ -> put $ cache { objects = V.snoc (objects cache) object }
RSymbol _ -> put $ cache { symbols = V.snoc (symbols cache) object }
_ -> return ()