StateVar-1.2.1: State variables
Copyright(c) Edward Kmett 2014-2019 Sven Panne 2009-2018
LicenseBSD3
MaintainerSven Panne <svenpanne@gmail.com>
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

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

Readable State Variables

class HasGetter t a | t -> a where Source #

This is the class of all readable state variables.

Methods

get :: MonadIO m => t -> m a Source #

Instances

Instances details
HasGetter (IO a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => IO a -> m a Source #

Storable a => HasGetter (Ptr a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => Ptr a -> m a Source #

Storable a => HasGetter (ForeignPtr a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => ForeignPtr a -> m a Source #

HasGetter (STM a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => STM a -> m a Source #

HasGetter (TVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => TVar a -> m a Source #

HasGetter (IORef a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => IORef a -> m a Source #

HasGetter (StateVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => StateVar a -> m a Source #

type GettableStateVar = IO Source #

A concrete implementation of a read-only state variable is simply an IO action to read the value.

makeGettableStateVar Source #

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

Instances details
Storable a => HasSetter (Ptr a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => Ptr a -> a -> m () Source #

Storable a => HasSetter (ForeignPtr a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => ForeignPtr a -> a -> m () Source #

HasSetter (TVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => TVar a -> a -> m () Source #

HasSetter (IORef a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => IORef a -> a -> m () Source #

HasSetter (SettableStateVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => SettableStateVar a -> a -> m () Source #

HasSetter (StateVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => StateVar a -> a -> m () 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

Instances details
Contravariant SettableStateVar Source # 
Instance details

Defined in Data.StateVar

HasSetter (SettableStateVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => SettableStateVar a -> a -> m () Source #

makeSettableStateVar 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.

default ($~) :: (MonadIO m, a ~ b, HasGetter t a) => t -> (a -> b) -> m () Source #

($~!) :: MonadIO m => t -> (a -> b) -> m () infixr 2 Source #

This is a variant of $~ which is strict in the transformed value.

default ($~!) :: (MonadIO m, a ~ b, HasGetter t a) => t -> (a -> b) -> m () Source #

Instances

Instances details
Storable a => HasUpdate (Ptr a) a a Source # 
Instance details

Defined in Data.StateVar

Methods

($~) :: MonadIO m => Ptr a -> (a -> a) -> m () Source #

($~!) :: MonadIO m => Ptr a -> (a -> a) -> m () Source #

Storable a => HasUpdate (ForeignPtr a) a a Source # 
Instance details

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 # 
Instance details

Defined in Data.StateVar

Methods

($~) :: MonadIO m => TVar a -> (a -> a) -> m () Source #

($~!) :: MonadIO m => TVar a -> (a -> a) -> m () Source #

HasUpdate (IORef a) a a Source # 
Instance details

Defined in Data.StateVar

Methods

($~) :: MonadIO m => IORef a -> (a -> a) -> m () Source #

($~!) :: MonadIO m => IORef a -> (a -> a) -> m () Source #

HasUpdate (StateVar a) a a Source # 
Instance details

Defined in Data.StateVar

Methods

($~) :: MonadIO m => StateVar a -> (a -> a) -> m () Source #

($~!) :: MonadIO m => StateVar a -> (a -> a) -> m () Source #

data StateVar 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 <- get v; v $= y; v $= x

should restore the previous state.

  • Ideally, in the absence of thrown exceptions:
v $= a >> get v

should return a, regardless of a. In practice some StateVars only permit a very limited range of value assignments, and do not report failure.

Constructors

StateVar (IO a) (a -> IO ()) 

Instances

Instances details
HasGetter (StateVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

get :: MonadIO m => StateVar a -> m a Source #

HasSetter (StateVar a) a Source # 
Instance details

Defined in Data.StateVar

Methods

($=) :: MonadIO m => StateVar a -> a -> m () Source #

HasUpdate (StateVar a) a a Source # 
Instance details

Defined in Data.StateVar

Methods

($~) :: MonadIO m => StateVar a -> (a -> a) -> m () Source #

($~!) :: MonadIO m => StateVar a -> (a -> a) -> m () Source #

makeStateVar Source #

Arguments

:: IO a

getter

-> (a -> IO ())

setter

-> StateVar a 

Construct a StateVar from two IO actions, one for reading and one for

mapStateVar :: (b -> a) -> (a -> b) -> StateVar a -> StateVar b Source #

Change the type of a StateVar