module Foreign.Store
(
writeStore
,newStore
,lookupStore
,readStore
,deleteStore
,storeAction
,withStore
,Store(..)
,StoreException(..))
where
import Control.Exception
import Data.Typeable
import Data.Word
import Foreign.Ptr
import Foreign.StablePtr
data StoreException
= StoreNotFound
deriving (Show,Eq,Typeable)
instance Exception StoreException
newtype Store a =
Store Word32
deriving (Show,Eq)
lookupStore :: Word32 -> IO (Maybe (Store a))
lookupStore i =
do r <- x_lookup i
if r == 0
then return Nothing
else return (Just (Store i))
newStore :: a -> IO (Store a)
newStore a =
do sptr <- newStablePtr a
i <- x_store sptr
return (Store i)
writeStore :: Store a -> a -> IO ()
writeStore (Store i) a =
do existing <- lookupStore i
maybe (return ()) deleteStore existing
sptr <- newStablePtr a
x_set i sptr
return ()
readStore :: Store a -> IO a
readStore (Store i) =
do sptr <- x_get i
if castStablePtrToPtr sptr == nullPtr
then throw StoreNotFound
else deRefStablePtr sptr
deleteStore :: Store a -> IO ()
deleteStore (Store i) = do
sptr <- x_get i
if castStablePtrToPtr sptr == nullPtr
then return ()
else do freeStablePtr sptr
x_delete i
storeAction :: Store a -> IO a -> IO a
storeAction s m =
do v <- m
writeStore s v
return v
withStore :: Store a -> (a -> IO b) -> IO b
withStore s f =
do v <- readStore s
f v
foreign import ccall
"x-helpers.h x_store"
x_store :: StablePtr a -> IO Word32
foreign import ccall
"x-helpers.h x_set"
x_set :: Word32 -> StablePtr a -> IO ()
foreign import ccall
"x-helpers.h x_get"
x_get :: Word32 -> IO (StablePtr a)
foreign import ccall
"x-helpers.h x_lookup"
x_lookup :: Word32 -> IO Word32
foreign import ccall
"x-helpers.h x_delete"
x_delete :: Word32 -> IO ()