module SAT.Mios.Data.Singleton
(
BoolSingleton
, newBool
, getBool
, setBool
, modifyBool
, IntSingleton
, newInt
, getInt
, setInt
, modifyInt
, DoubleSingleton
, newDouble
, getDouble
, setDouble
, modifyDouble
)
where
import qualified Data.Vector.Unboxed.Mutable as UV
type IntSingleton = UV.IOVector Int
newInt :: Int -> IO IntSingleton
newInt k = do
s <- UV.new 1
UV.unsafeWrite s 0 k
return s
getInt :: IntSingleton -> IO Int
getInt val = UV.unsafeRead val 0
setInt :: IntSingleton -> Int -> IO ()
setInt val !x = UV.unsafeWrite val 0 x
modifyInt :: IntSingleton -> (Int -> Int) -> IO ()
modifyInt val f = UV.unsafeModify val f 0
type BoolSingleton = UV.IOVector Bool
newBool :: Bool -> IO BoolSingleton
newBool b = do
s <- UV.new 1
UV.unsafeWrite s 0 b
return s
getBool :: BoolSingleton -> IO Bool
getBool val = UV.unsafeRead val 0
setBool :: BoolSingleton -> Bool -> IO ()
setBool val !x = UV.unsafeWrite val 0 x
modifyBool :: BoolSingleton -> (Bool -> Bool) -> IO ()
modifyBool val f = UV.unsafeModify val f 0
type DoubleSingleton = UV.IOVector Double
newDouble :: Double -> IO DoubleSingleton
newDouble d = do
s <- UV.new 1
UV.unsafeWrite s 0 d
return s
getDouble :: DoubleSingleton -> IO Double
getDouble val = UV.unsafeRead val 0
setDouble :: DoubleSingleton -> Double -> IO ()
setDouble val !x = UV.unsafeWrite val 0 x
modifyDouble :: DoubleSingleton -> (Double -> Double) -> IO ()
modifyDouble val f = UV.unsafeModify val f 0