| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Lens.Mutable
Synopsis
- data PrimOpGroup
- data S p s = S !(State# s)
- type LST p s r = S p s -> (r, S p s)
- class FromLST p s m where
- class FromLST p s m => IsoLST p s m where
- type MonadLST p s m = (FromLST p s m, Monad m)
- type SLens p s a = Lens' (S p s) a
- type ASLens p s a = ALens' (S p s) a
- runSLens :: FromLST p s m => LensLike' ((,) r) (S p s) a -> (a -> (r, a)) -> m r
- runASLens :: FromLST p s m => ALens' (S p s) a -> (a -> (r, a)) -> m r
- stateRead :: a -> (a, a)
- stateWrite :: b -> a -> ((), b)
- stateModify :: (a -> b) -> a -> ((), b)
- class AsLens s a ref where
- class AsLens s a ref => Allocable s a ref where- alloc :: a -> s -> (ref a, s)
- free :: HasCallStack => ref a -> s -> (a, s)
- isValid :: ref a -> s -> (Bool, s)
 
Foundations
data PrimOpGroup Source #
GHC implements different primitive operations, some of which cannot be
 mixed together and some of which can only be run in certain contexts. In
 particular, STM-related primops cannot be run directly in the IO monad.
 However, this restriction is not represented at the bottom layer of the IO
 runtime which we need to wrap around and expose to users.
This data structure is our ad-hoc attempt to group together "compatible" primops so that only lens representing compatible references can be composed together, avoiding deadly segfaults.
See https://gitlab.haskell.org/ghc/ghc/blob/master/compiler/prelude/primops.txt.pp
See also https://github.com/haskell/primitive/issues/43#issuecomment-613771394
Instances
Lifted State#. This is needed to interoperate lifted ("normal") types
 and unlifted types (such as primitives), but it also gives us the chance to
 restrict composition based on PrimOpGroup which sadly isn't done in the
 unlifted internal representation, though it could be.
Instances
| Allocable (S 'OpST RealWorld) a IORef Source # | |
| Allocable (S 'OpMVar RealWorld) a MVar Source # | |
| Allocable (S 'OpSTM RealWorld) a TMVar Source # | |
| Allocable (S 'OpSTM RealWorld) a TVar Source # | |
| AsLens (S 'OpST RealWorld) a IORef Source # | |
| AsLens (S 'OpMVar RealWorld) a MVar Source # | View a  Note: when this is eventually run in  If you don't want to deal with this, don't use an  | 
| AsLens (S 'OpSTM RealWorld) a TMVar Source # | |
| AsLens (S 'OpSTM RealWorld) a TVar Source # | |
| Allocable (S 'OpST s) a (STRef s) Source # | |
| Allocable (S 'OpST s) a (MutVar s) Source # | |
| AsLens (S 'OpST s) a (STRef s) Source # | |
| AsLens (S 'OpST s) a (MutVar s) Source # | |
type LST p s r = S p s -> (r, S p s) Source #
A lifted primitive state-transformer that interoperates with lens.
Specifically, this is a bare (unwrapped in StateT) state transition on a
 lifted ("normal") state type.
To obtain one of these, you may apply a SLens p s a(a -> (r, a)).
class FromLST p s m where Source #
Convert an LST pm.
This is similar to PrimMonad from the primitives package except our
 extra p type-param helps us avoid accidentally mixing incompatible primops.
class FromLST p s m => IsoLST p s m where Source #
Convert an LST pm.
This is similar to PrimBase from the primitives package except our extra
 p type-param helps us avoid accidentally mixing incompatible primops.
type MonadLST p s m = (FromLST p s m, Monad m) Source #
Convert an 'LST p from some monadic action m.
type SLens p s a = Lens' (S p s) a Source #
Representation of a mutable reference as a Lens'.
When the lens functor type-param is (,) r, then the output transition
 function is of type LST s rstToM.
Again, in principle this ought not to be necessary, but the Haskell runtime forces us to do this due to historical design decisions to hide necessary details that seemed appropriate to hide at the time.
Convenience utilities
runSLens :: FromLST p s m => LensLike' ((,) r) (S p s) a -> (a -> (r, a)) -> m r Source #
Run a bare state transition on a lens in the monad for p.
The lens may be an SLens p
runASLens :: FromLST p s m => ALens' (S p s) a -> (a -> (r, a)) -> m r Source #
Run a bare state transition on an ALens' in the monad for p.
stateWrite :: b -> a -> ((), b) Source #
A bare state transition representing a write operation.
stateWrite brunSLens to write b to the reference.
stateModify :: (a -> b) -> a -> ((), b) Source #
A bare state transition representing a modify/map operation.
stateModify frunSLens to apply f to the reference.
Typeclasses and instances
class AsLens s a ref where Source #
Convert a reference type to a Lens'.
Instances
| AsLens (S 'OpST RealWorld) a IORef Source # | |
| AsLens (S 'OpMVar RealWorld) a MVar Source # | View a  Note: when this is eventually run in  If you don't want to deal with this, don't use an  | 
| AsLens (S 'OpSTM RealWorld) a TMVar Source # | |
| AsLens (S 'OpSTM RealWorld) a TVar Source # | |
| AsLens (S 'OpST s) a (STRef s) Source # | |
| AsLens (S 'OpST s) a (MutVar s) Source # | |
class AsLens s a ref => Allocable s a ref where Source #
A state in which you can allocate new references.
This can be defined on either pure or impure references. For pure references
 one could e.g. define an instance of this on Map k v with Const k as the
 reference type - see unit tests for an example.
Minimal complete definition
Methods
alloc :: a -> s -> (ref a, s) Source #
Allocate a new reference with the given value.
free :: HasCallStack => ref a -> s -> (a, s) Source #
Deallocate an existing reference, and return its value.
The default implementation simply writes error into the reference and
  returns the old value. The caller is responsible for actually throwing away
  the reference and never using it again, as per Haskell's GC semantics.
isValid :: ref a -> s -> (Bool, s) Source #
Check if a reference is valid.
The default implementation simply forces the reference and returns True. If
  the reference has already been freed (via free) then an error will be
  raised, which you can catch in the IO monad as per usual. In other words,
  the default implementation will never return False.