module Ros.Internal.Util.StorableMonad (peek, poke, runStorable,
StorableM) where
import Control.Monad.State.Strict
import Foreign.Ptr
import Foreign.Storable hiding (peek, poke)
import qualified Foreign.Storable as S
type StorableM a = StateT (Ptr ()) IO a
poke :: Storable a => a -> StorableM ()
poke x = do ptr <- get
liftIO $ S.poke (castPtr ptr) x
put (plusPtr ptr (sizeOf x))
peek :: Storable a => StorableM a
peek = do ptr <- get
x <- liftIO $ S.peek (castPtr ptr)
put (plusPtr ptr (sizeOf x))
return x
runStorable :: StorableM a -> Ptr b -> IO a
runStorable s p = evalStateT s (castPtr p)