Portability | portable |
---|---|
Stability | stable |
Maintainer | Sven Panne <svenpanne@gmail.com> |
Safe Haskell | Safe-Inferred |
State variables are references in the IO monad, like IORef
s or parts of
the OpenGL state. Note that state variables are not neccessarily writable or
readable, they may come in read-only or write-only flavours, too. As a very
simple example for a state variable, consider an explicitly allocated memory
buffer. This buffer can easily be converted into a StateVar
:
makeStateVarFromPtr :: Storable a => Ptr a -> StateVar a makeStateVarFromPtr p = makeStateVar (peek p) (poke p)
The example below puts 11 into a state variable (i.e. into the buffer), increments the contents of the state variable by 22, and finally prints the resulting content:
do p <- malloc :: IO (Ptr Int) let v = makeStateVarFromPtr p v $= 11 v $~ (+ 22) x <- get v print x
IORef
s are state variables, too, so an example with them looks extremely
similiar:
do v <- newIORef (0 :: Int) v $= 11 v $~ (+ 22) x <- get v print x
- class HasGetter g where
- data GettableStateVar a
- makeGettableStateVar :: IO a -> GettableStateVar a
- class HasSetter s where
- data SettableStateVar a
- makeSettableStateVar :: (a -> IO ()) -> SettableStateVar a
- data StateVar a
- makeStateVar :: IO a -> (a -> IO ()) -> StateVar a
- ($~) :: (HasGetter v, HasSetter v) => v a -> (a -> a) -> IO ()
- ($=!) :: HasSetter s => s a -> a -> IO ()
- ($~!) :: (HasGetter v, HasSetter v) => v a -> (a -> a) -> IO ()
Readable State Variables
The class of all readable state variables.
data GettableStateVar a Source
A concrete implementation of a read-only state variable, carrying an IO action to read the value.
makeGettableStateVar :: IO a -> GettableStateVar aSource
Construct a GettableStateVar
from an IO action.
Writable State Variables
The class of all writable state variables.
data SettableStateVar a Source
A concrete implementation of a write-only state variable, carrying an IO action to write the new value.
makeSettableStateVar :: (a -> IO ()) -> SettableStateVar aSource
Construct a SettableStateVar
from an IO action.
General State Variables
A concrete implementation of a readable and writable state variable, carrying one IO action to read the value and another IO action to write the new value.
makeStateVar :: IO a -> (a -> IO ()) -> StateVar aSource
Construct a StateVar
from two IO actions, one for reading and one for
writing.
Utility Functions
($~) :: (HasGetter v, HasSetter v) => v a -> (a -> a) -> IO ()Source
A modificator convenience function, transforming the contents of a state variable with a given funtion.