| Copyright | (c) Edward Kmett 2014-2019 Sven Panne 2009-2018 | 
|---|---|
| License | BSD3 | 
| Maintainer | Sven Panne <svenpanne@gmail.com> | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Data.StateVar
Description
State variables are references in the IO monad, like IORefs 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 could 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
However, Ptr can be used directly through the same API:
  do p <- malloc :: IO (Ptr Int)
     p $= 11
     p $~ (+ 22)
     x <- get p
     print x
IORefs 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
Synopsis
- class HasGetter t a | t -> a where
- type GettableStateVar = IO
- makeGettableStateVar :: IO a -> GettableStateVar a
- class HasSetter t a | t -> a where
- ($=!) :: (HasSetter t a, MonadIO m) => t -> a -> m ()
- newtype SettableStateVar a = SettableStateVar (a -> IO ())
- makeSettableStateVar :: (a -> IO ()) -> SettableStateVar a
- class HasSetter t b => HasUpdate t a b | t -> a b where
- data StateVar a = StateVar (IO a) (a -> IO ())
- makeStateVar :: IO a -> (a -> IO ()) -> StateVar a
- mapStateVar :: (b -> a) -> (a -> b) -> StateVar a -> StateVar b
Readable State Variables
class HasGetter t a | t -> a where Source #
This is the class of all readable state variables.
Instances
| HasGetter (IO a) a Source # | |
| Storable a => HasGetter (Ptr a) a Source # | |
| Storable a => HasGetter (ForeignPtr a) a Source # | |
| Defined in Data.StateVar Methods get :: MonadIO m => ForeignPtr a -> m a Source # | |
| HasGetter (STM a) a Source # | |
| HasGetter (TVar a) a Source # | |
| HasGetter (IORef a) a Source # | |
| HasGetter (StateVar a) a Source # | |
type GettableStateVar = IO Source #
A concrete implementation of a read-only state variable is simply an IO action to read the value.
Arguments
| :: IO a | getter | 
| -> GettableStateVar a | 
Construct a GettableStateVar from an IO action.
Writable State Variables
class HasSetter t a | t -> a where Source #
This is the class of all writable state variables.
Methods
($=) :: MonadIO m => t -> a -> m () infixr 2 Source #
Write a new value into a state variable.
Instances
| Storable a => HasSetter (Ptr a) a Source # | |
| Storable a => HasSetter (ForeignPtr a) a Source # | |
| Defined in Data.StateVar Methods ($=) :: MonadIO m => ForeignPtr a -> a -> m () Source # | |
| HasSetter (TVar a) a Source # | |
| HasSetter (IORef a) a Source # | |
| HasSetter (SettableStateVar a) a Source # | |
| Defined in Data.StateVar Methods ($=) :: MonadIO m => SettableStateVar a -> a -> m () Source # | |
| HasSetter (StateVar a) a Source # | |
($=!) :: (HasSetter t a, MonadIO m) => t -> a -> m () infixr 2 Source #
This is a variant of $= which is strict in the value to be set.
newtype SettableStateVar a Source #
A concrete implementation of a write-only state variable, carrying an IO action to write the new value.
Constructors
| SettableStateVar (a -> IO ()) | 
Instances
| Contravariant SettableStateVar Source # | |
| Defined in Data.StateVar Methods contramap :: (a -> b) -> SettableStateVar b -> SettableStateVar a # (>$) :: b -> SettableStateVar b -> SettableStateVar a # | |
| HasSetter (SettableStateVar a) a Source # | |
| Defined in Data.StateVar Methods ($=) :: MonadIO m => SettableStateVar a -> a -> m () Source # | |
Arguments
| :: (a -> IO ()) | setter | 
| -> SettableStateVar a | 
Construct a SettableStateVar from an IO action for writing.
Updatable State Variables
class HasSetter t b => HasUpdate t a b | t -> a b where Source #
This is the class of all updatable state variables.
Minimal complete definition
Nothing
Methods
($~) :: MonadIO m => t -> (a -> b) -> m () infixr 2 Source #
Transform the contents of a state variable with a given funtion.
($~) :: (MonadIO m, a ~ b, HasGetter t a) => t -> (a -> b) -> m () infixr 2 Source #
Transform the contents of a state variable with a given funtion.
($~!) :: MonadIO m => t -> (a -> b) -> m () infixr 2 Source #
This is a variant of $~ which is strict in the transformed value.
($~!) :: (MonadIO m, a ~ b, HasGetter t a) => t -> (a -> b) -> m () infixr 2 Source #
This is a variant of $~ which is strict in the transformed value.
Instances
| Storable a => HasUpdate (Ptr a) a a Source # | |
| Storable a => HasUpdate (ForeignPtr a) a a Source # | |
| Defined in Data.StateVar Methods ($~) :: MonadIO m => ForeignPtr a -> (a -> a) -> m () Source # ($~!) :: MonadIO m => ForeignPtr a -> (a -> a) -> m () Source # | |
| HasUpdate (TVar a) a a Source # | |
| HasUpdate (IORef a) a a Source # | |
| HasUpdate (StateVar a) a a Source # | |
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. This data type represents a piece of mutable, imperative state with possible side-effects. These tend to encapsulate all sorts tricky behavior in external libraries, and may well throw exceptions. Inhabitants should satsify the following properties:
- In the absence of concurrent mutation from other threads or a thrown exception:
do x <-getv; v$=y; v$=x
should restore the previous state.
- Ideally, in the absence of thrown exceptions:
v$=a >>getv
should return a, regardless of a. In practice some StateVars only
 permit a very limited range of value assignments, and do not report failure.
Construct a StateVar from two IO actions, one for reading and one for