Copyright | (c) Justin Le 2020 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Mutable
Description
Main entrypoint of the package. Abstract over different types for piecewise-mutable references of values.
See https://mutable.jle.im/ for a comprehensive introduction.
Synopsis
- class Mutable s a where
- type Ref s a = (v :: Type) | v -> a s
- thawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (Ref s a)
- freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> m a
- copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> a -> m ()
- moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> Ref s a -> m ()
- cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> m (Ref s a)
- unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (Ref s a)
- unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> m a
- modifyRef :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> a) -> m ()
- modifyRef' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> a) -> m ()
- updateRef :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> (a, b)) -> m b
- updateRef' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> (a, b)) -> m b
- newtype RefFor s a = RefFor {}
- class DefaultMutable s a r | r -> a s
- data GRef s a
- data MutVar s a
- newtype CoerceRef s b a = CoerceRef {
- getCoerceRef :: Ref s a
- newtype TraverseRef s f a = TraverseRef {
- getTraverseRef :: f (Ref s a)
- newtype GMutableRef s f a = GMutableRef {
- getGMutableRef :: GRef_ s f a
- newtype RecRef s f a = RecRef {}
- data HListRef :: Type -> [Type] -> Type where
- data UnitRef s = UnitRef
- data VoidRef s
- newtype VarMut a = VarMut {
- getVarMut :: a
- newtype CoerceMut s a = CoerceMut {
- getCoerceMut :: s
- newtype TraverseMut f a = TraverseMut {
- getTraverseMut :: f a
- newtype Immutable s a = Immutable {
- getImmutable :: a
- newtype MutPart s b a = MutPart {
- getMutPart :: Ref s b -> Ref s a
- withPart :: MutPart s b a -> Ref s b -> (Ref s a -> m r) -> m r
- freezePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> m a
- copyPart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> a -> m ()
- movePartInto :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> Ref s a -> m ()
- movePartOver :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s a -> Ref s b -> m ()
- movePartWithin :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> Ref s b -> m ()
- clonePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> m (Ref s a)
- unsafeFreezePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> m a
- modifyPart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> a) -> m ()
- modifyPart' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> a) -> m ()
- updatePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> (a, r)) -> m r
- updatePart' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> (a, r)) -> m r
- class (Mutable s b, Mutable s a) => FieldMut (fld :: Symbol) s b a | fld b -> a where
- withField :: FieldMut fld s b a => Label fld -> Ref s b -> (Ref s a -> m r) -> m r
- mutField :: forall fld s b a. FieldMut fld s b a => Label fld -> Ref s b -> Ref s a
- data Label (a :: Symbol) = Label
- class (Mutable s b, Mutable s a) => PosMut (i :: Nat) s b a | i b -> a where
- withPos :: forall i s m b a r. PosMut i s b a => Ref s b -> (Ref s a -> m r) -> m r
- mutPos :: forall i s b a. PosMut i s b a => Ref s b -> Ref s a
- class (Mutable s b, Mutable s a) => TupleMut s b a | b -> a where
- withTuple :: TupleMut s b a => Ref s b -> (Ref s a -> m r) -> m r
- hkdMutParts :: forall z s. (Generic (z (RefFor s)), Generic (z (MutPart s (z Identity))), HKDMutParts s z (Rep (z (RefFor s))) (Rep (z (MutPart s (z Identity))))) => z (MutPart s (z Identity))
- class (Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z i o
- mutFst :: MutPart s (a, b) a
- mutSnd :: MutPart s (a, b) b
- mutRec :: forall a as f rec s. (Ref s (rec f as) ~ rec (RecRef s f) as, RecElem rec a a as as (RIndex a as), RecElemFCtx rec (RecRef s f)) => MutPart s (rec f as) (f a)
- coerceRef :: Ref s b ~ CoerceRef s b a => MutPart s b a
- withCoerceRef :: CoerceRef s b a -> (Ref s a -> m r) -> m r
- data MutBranch s b a = MutBranch {}
- thawBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> a -> m (Ref s b)
- freezeBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m (Maybe a)
- moveBranch :: (Mutable s b, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> Ref s a -> m ()
- copyBranch :: (Mutable s b, Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> a -> m ()
- cloneBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m (Maybe (Ref s a))
- hasBranch :: (PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m Bool
- hasn'tBranch :: (PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m Bool
- unsafeThawBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> a -> m (Ref s b)
- unsafeFreezeBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m (Maybe a)
- withBranch :: (PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> (Ref s a -> m r) -> m (Maybe r)
- withBranch_ :: (PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> (Ref s a -> m r) -> m ()
- modifyBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> (a -> a) -> m ()
- modifyBranch' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> (a -> a) -> m ()
- updateBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> (a -> (a, r)) -> m (Maybe r)
- updateBranch' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> (a -> (a, r)) -> m (Maybe r)
- constrMB :: forall ctor s b a. (Ref s b ~ GRef s b, GMutBranchConstructor ctor s (Rep b) a) => CLabel ctor -> MutBranch s b a
- data CLabel (ctor :: Symbol) = CLabel
- class (GMutable s f, Mutable s a) => GMutBranchConstructor (ctor :: Symbol) s f a | ctor f -> a
- type family MapRef s as where ...
- nilMB :: Mutable s a => MutBranch s [a] ()
- consMB :: Mutable s a => MutBranch s [a] (a, [a])
- nothingMB :: Mutable s a => MutBranch s (Maybe a) ()
- justMB :: Mutable s a => MutBranch s (Maybe a) a
- leftMB :: (Mutable s a, Mutable s b) => MutBranch s (Either a b) a
- rightMB :: (Mutable s a, Mutable s b) => MutBranch s (Either a b) b
- class Monad m => PrimMonad (m :: Type -> Type)
- type family PrimState (m :: Type -> Type)
Documentation
class Mutable s a where Source #
An instance of
means that Mutable
s aa
can be stored
a mutable reference in a PrimMonad
m
(where s
is the mutable state
token PrimState
of that monad).
The associated type
links any Ref
s aa
to the type of its
canonical mutable version.
The benefit of this typeclass, instead of just using
IORef
or MutVar
or specific mutable versions like
Vector
and MVector
, is two-fold:
- Piecewise-mutable values, so you can write to only one part and not
others. This also allows for cheaper "writes", even if you replace
the whole value: you don't need to ever synthesize an entire new
value, you can keep each component in a separate variable until you
freezeRef
it out. This can be especially useful for composite data types containing large structures likeVector
. Generic abstractions (similar to
Show
), so you can automatically derive instances while preserving piecewise-ness. For example, the instanceinstance (Mutable s a, Mutable s b) => Mutable s (a, b)
If
a
andb
are piecwise-mutable, then the instance here will appropriately utilize that fact.
To modify the specific parts of mutable values, it can be useful to use the functions in Data.Mutable.Parts.
There are facilities to automatically piecewise mutable versions for
user-defined instances of Generic
.
For example, if we have a type like:
data TwoVectors = TV { tvInt ::Vector
Int , tvDouble :: Vector Double } deriving Generic instance Mutable s TwoVectors where type Ref s TwoVectors =GRef
s TwoVectors
Then now we get:
thawRef
:: TwoVectors -> m (GRef
s TwoVectors)freezeRef
::GRef
s TwoVectors -> m TwoVectors
And
is now a piecewise-mutable reference storing each
part in a way that can be modified separately (for example, with tools
from Data.Mutable.Parts). It does this by internally allocating two
GRef
s TwoVectorsMVector
s. If the two vectors are large, this can be much more
efficient to modify (if you are modifying several times) than by just
doing alterations on TwoVector
s. It is also much better for large
vectors if you plan on modifying only a single item in the vector.
If you are using the "higher-kinded" data pattern, a la https://reasonablypolymorphic.com/blog/higher-kinded-data/, then we can also do:
data TwoVectors f = TV { tvInt ::HKD
f (Vector
Int) , tvDouble :: HKD f (Vector Double) } deriving Generic instance Mutable (TwoVectorsIdentity
) where type Ref (TwoVectorsIdentity
) = TwoVectors (RefFor
s)
And now your mutable ref is literally going to be a product of the components
ghci> tvr@(TV is ds) <- thawRef (TV xs ys) ghci> :t tvr TV (RefFor
RealWorld
) ghci> :t isMVector
RealWorld Int ghci> :t ds MV.MVector RealWorld Double
So thawRef
will actually just get you the same record type but with
the mutable versions of each field. If you modify the mutable fields,
and then later freezeRef
the whole thing, the resulting frozen value
will incorporate all of the changes to the individual fields.
In addition, there are a few more "automatically derived" instances you
can get by picking Ref
:
-- Make a mutable version for any newtype wrapper, using the Mutable
-- of the underlying type
newtype MyType = MT (Vector Double)
type Ref s MyType = CoerceRef s MyType (Vector Double)
-- Make a mutable version of any container, where the items are all
-- mutable references.
data MyContainer a = MC a a a a
deriving (Functor, Foldable, Traversable)
type Ref s (MyContainer a) = TraverseRef s MyContainer a
See https://mutable.jle.im/02-mutable-and-ref.html for more information on this typeclass and how to define instances automatically, and also
- https://mutable.jle.im/05-mutable-parts.html for more information on dealing with record types
- https://mutable.jle.im/06-mutable-branches for more information on dealing with sum types
Minimal complete definition
Nothing
Associated Types
type Ref s a = (v :: Type) | v -> a s Source #
Links the type a
to the type of its canonical "mutable version".
For example, for Vector
, the mutable version is MVector
, so
we have
type Ref s (Vector
a) =MVector
s a
This means that using thawRef
on a Vector
will give you an
MVector
, using freezeRef
on a Vector
will give you
a Vector
, etc.
thawRef
:: (PrimMonad
m,PrimState
m ~ s) =>Vector
a -> m (Vector
s a)freezeRef
:: (PrimMonad
m,PrimState
m ~ s) =>Vector
s a -> m (Vector
a)copyRef
:: (PrimMonad
m,PrimState
m ~ s) =>Vector
s a ->Vector
a -> m ()
This associated type must be unique for a
, so no two types a
can
have the same
. This makes type inference a lot more
useful: if you use Ref
s afreezeRef
on an MVector
, for instance, the
return type will be inferred to be Vector
.
The default instance is just a plain old MutVar
containing the
type. This is a valid instance, but it treats the entire type
"wholesale" --- it is basically using it as a non-mutable type. You
won't get any of the performance benefits of piecewise mutation from
it, but it is useful as a base case for non-composite types like
Int
.
There are some built-in alternative options for user-defined ADTs
with Generic
instances:
-- Works for allGeneric
instances, preserves piecewise mutation -- for products type Ref s a =GRef
s a
If you just set up a blank instance, the implementations of
thawRef
, freezeRef
, and copyRef
will be inferred using
DefaultMutable
.
data MyType -- The default setup is OK instance Mutable s MyType -- This is equivalent to the above instance Mutable s MyType type Ref s MyType =MutVar
s MyType -- anyGeneric
instance data MyType = MyType { mtInt :: Int, mtDouble :: Double } deriving Generic instance Mutable s MyType where type Ref s MyType =GRef
s MyType
See https://mutable.jle.im/02-mutable-and-ref.html for more information on this type family and how to define instances automatically.
Note that this type synonym ins injective --- this means that if you
write a function polymorphic over
, you can always infer
Ref
s as
and a
(the value stored in the Ref
).
In practice, if you want to write your own instance from scratch,
the consequence is that you must have the s
type variable
somewhere in your type (see UnitRef
and VoidRef
for examples).
Methods
thawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (Ref s a) Source #
Thaw a pure/persistent value into its mutable version, which can
be manipulated using modifyRef
or other methods
specific for that type (like read
).
Returns the Ref
instance, so, for example, for Vector
:
thawRef
:: (PrimMonad
m,PrimState
m ~ s) =>Vector
a -> m (Vector
s a)
For non-composite (like Int
), this is often called the "new var"
function, like newIORef
/ newSTRef
/ newMutVar
etc.
default thawRef :: (DefaultMutable s a (Ref s a), PrimMonad m, PrimState m ~ s) => a -> m (Ref s a) Source #
freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> m a Source #
Freeze a mutable value into its pure/persistent version.
Takes a Ref
instance, but type inference will be able to infer the
pure value's type because Ref
is injective.
For example, for Vector
:
freezeRef
:: (PrimMonad
m,PrimState
m ~ s) =>Vector
s a -> m (Vector
a)
For non-composite (like Int
), this is often called the "read var"
function, like readIORef
/ readSTRef
/ readMutVar
etc.
default freezeRef :: (DefaultMutable s a (Ref s a), PrimMonad m, PrimState m ~ s) => Ref s a -> m a Source #
Overwrite a mutable value by provivding a pure/persistent value.
copyRef
Returns the Ref
and the value, so, for example, for Vector
:
copyRef
:: (PrimMonad
m,PrimState
m ~ s) =>Vector
s a ->Vector
a -> m ()
Note that if a
is a composite type (with an appropriate composite
reference), this will be done "piecewise": it'll write to each
mutable component separately.
For non-composite (like Int
), this is often called the "write var"
function, like writeIORef
/ writeSTRef
/ writeMutVar
etc.
default copyRef :: (DefaultMutable s a (Ref s a), PrimMonad m, PrimState m ~ s) => Ref s a -> a -> m () Source #
Deep Copy-move a mutable reference on top of another, overwriting the second one.
For non-composite types, this is the same as a thawRef
and
a copyRef
. For composite types this can be more effficient
because the copying is done piecewise, so the intermediate pure value
is never created.
default moveRef :: (DefaultMutable s a (Ref s a), PrimMonad m, PrimState m ~ s) => Ref s a -> Ref s a -> m () Source #
cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> m (Ref s a) Source #
Create a deep copy of a mutable reference, allocated to a separate independent reference.
For non-composite types, this is the same as a thawRef
and
a freezeRef
. For composite types this can be more effficient
because the cloning is done piecewise, so the intermediate pure value
is never created.
default cloneRef :: (DefaultMutable s a (Ref s a), PrimMonad m, PrimState m ~ s) => Ref s a -> m (Ref s a) Source #
unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (Ref s a) Source #
A non-copying version of thawRef
that can be more efficient for
types where the mutable representation is the same as the immutable
one (like Vector
).
This is safe as long as you never again use the original pure value, since it can potentially directly mutate it.
default unsafeThawRef :: (DefaultMutable s a (Ref s a), PrimMonad m, PrimState m ~ s) => a -> m (Ref s a) Source #
unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s a -> m a Source #
A non-copying version of freezeRef
that can be more efficient for
types where the mutable representation is the same as the immutable
one (like Vector
).
This is safe as long as you never again modify the mutable reference, since it can potentially directly mutate the frozen value magically.
default unsafeFreezeRef :: (DefaultMutable s a (Ref s a), PrimMonad m, PrimState m ~ s) => Ref s a -> m a Source #
Instances
modifyRef :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> a) -> m () Source #
Apply a pure function on an immutable value onto a value stored in a mutable reference.
modifyRef' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> a) -> m () Source #
modifyRef
, but forces the result before storing it back in the
reference.
updateRef :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> (a, b)) -> m b Source #
Apply a pure function on an immutable value onto a value stored in a mutable reference, returning a result value from that function.
updateRef' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> (a, b)) -> m b Source #
updateRef
, but forces the updated value before storing it back in the
reference.
A handy newtype wrapper that allows you to partially apply Ref
.
is the same as RefFor
m a
, but can be partially applied.Ref
s a
If used with HKD
, you can treat this syntactically identically as
a
.Ref
s a
Instances
Instances
class DefaultMutable s a r | r -> a s Source #
The default implementations of thawRef
, freezeRef
, and copyRef
dispatched for different choices of Ref
.
Basically, by specifying Ref
, you get the rest of the instance for
free.
We have the default case:
-- default, if you don't specify Ref
instance Mutable s MyType
-- the above is the same as:
instance Mutable s MyType
type Ref s MyType = MutVar s) MyType
The case for any instance of Generic
:
instance Mutable s MyType type Ref s MyType = GRef s MyType
The case for the "higher-kinded data" pattern a la https://reasonablypolymorphic.com/blog/higher-kinded-data/:
instance Mutable s (MyTypeF Identity) type Ref s (MyTypeF Identity) = MyTypeF (RefFor s)
The case for any newtype wrapper:
newtype MyType = MT (Vector Double) instance Mutable s MyType where type Ref s MyType = CoerceRef s MyType (Vector Double)
And the case for any 'Traversable instance, where the items will all be mutable references:
data MyContainer a = MC a a a a deriving (Functor, Foldable, Traversable) instance Mutable s a => Mutable s (MyContainer a) where type Ref s (MyContainer a) = TraverseRef s MyContainer a
Minimal complete definition
defaultThawRef, defaultFreezeRef, defaultCopyRef, defaultMoveRef, defaultCloneRef, defaultUnsafeThawRef, defaultUnsafeFreezeRef
Instances
Automatically generate a piecewise mutable reference for any Generic
instance.
-- | anyGeneric
instance data MyType = MyType { mtInt :: Int, mtDouble :: Double } deriving (Generic, Show) instance Mutable s MyType where type Ref s MyType =GRef
s MyType
ghci> r <-thawRef
(MyType 3 4.5) ghci>freezeRef
r MyType 3 4.5 ghci>freezePart
(fieldMut
#mtInt) r 3 ghci>copyPart
(fieldMut #mtDouble) 1.23 ghci> freezeRef r MyType 3 1.23
Note that this is basically just a bunch of tupled refs for a product type. For a sum type (with multiple constructors), an extra layer of indirection is added to account for the dynamically changable shape.
See Data.Mutable.Parts and Data.Mutable.Branches for nice ways to inspect and mutate the internals of this type (as demonstrated above).
If the facilities in those modules are not adequate, you can also
manually crack open GRef
and work with the internals. Getting the
type of
should allow you to navigate what is going
on, if you are familiar with GHC.Generics. However, ideally, you
would never need to do this.unGRef
@MyType
Instances
(Generic a, GMutable s (Rep a)) => DefaultMutable s a (GRef s a) Source # | |
Defined in Data.Mutable.Internal Methods defaultThawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (GRef s a) Source # defaultFreezeRef :: (PrimMonad m, PrimState m ~ s) => GRef s a -> m a Source # defaultCopyRef :: (PrimMonad m, PrimState m ~ s) => GRef s a -> a -> m () Source # defaultMoveRef :: (PrimMonad m, PrimState m ~ s) => GRef s a -> GRef s a -> m () Source # defaultCloneRef :: (PrimMonad m, PrimState m ~ s) => GRef s a -> m (GRef s a) Source # defaultUnsafeThawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (GRef s a) Source # defaultUnsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => GRef s a -> m a Source # | |
Eq (GRef_ s (Rep a) ()) => Eq (GRef s a) Source # | |
Ord (GRef_ s (Rep a) ()) => Ord (GRef s a) Source # | |
Defined in Data.Mutable.Internal |
A MutVar
behaves like a single-element mutable array associated
with a primitive state token.
Instances
DefaultMutable s a (MutVar s a) Source # | |
Defined in Data.Mutable.Internal Methods defaultThawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (MutVar s a) Source # defaultFreezeRef :: (PrimMonad m, PrimState m ~ s) => MutVar s a -> m a Source # defaultCopyRef :: (PrimMonad m, PrimState m ~ s) => MutVar s a -> a -> m () Source # defaultMoveRef :: (PrimMonad m, PrimState m ~ s) => MutVar s a -> MutVar s a -> m () Source # defaultCloneRef :: (PrimMonad m, PrimState m ~ s) => MutVar s a -> m (MutVar s a) Source # defaultUnsafeThawRef :: (PrimMonad m, PrimState m ~ s) => a -> m (MutVar s a) Source # defaultUnsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => MutVar s a -> m a Source # | |
Eq (MutVar s a) | |
newtype CoerceRef s b a Source #
A Ref
that works by using the Mutable
instance of an equivalent
type. This is useful for newtype wrappers, so you can use the
underlying data type's Mutable
instance.
newtype MyVec = MyVec (Vector
Double) instanceMutable
s MyVec where typeRef
s MyVec =CoerceRef
s s (Vector
Double)
The Ref s MyVec
uses the a
under the hood.MVector
Double
It's essentially a special case of GRef
for newtypes.
Constructors
CoerceRef | |
Fields
|
Instances
newtype TraverseRef s f a Source #
A Ref
that works for any instance of Traversable
, by using the
fields of the Traversable
instance to purely store mutable references.
Note that this really only makes complete sense if the Traversable
is
fixed-size, or you never modify the length of the traversable as you use
it as a reference.
If you do modify the length, copying and modifying semantics can be a bit funky:
- If copying a shorter item into a longer item ref, the "leftovers" items in the longer item are unchanged.
- If copying a longer item into a shorter item ref, the leftover items are unchanged.
ghci> r <-thawTraverse
[1..10] ghci>copyTraverse
r [0,0,0,0] ghci>freezeTraverse
r [0,0,0,0,5,6,7,8,9,10] ghci>copyTraverse
r [20..50] ghci>freezeTraverse
r [20,21,22,23,24,25,26,27,28,29]
Constructors
TraverseRef | |
Fields
|
Instances
newtype GMutableRef s f a Source #
A Ref
for instances of GMutable
, which are the GHC.Generics
combinators.
Constructors
GMutableRef | |
Fields
|
Instances
Eq (GRef_ s f a) => Eq (GMutableRef s f a) Source # | |
Defined in Data.Mutable.Internal Methods (==) :: GMutableRef s f a -> GMutableRef s f a -> Bool # (/=) :: GMutableRef s f a -> GMutableRef s f a -> Bool # | |
Ord (GRef_ s f a) => Ord (GMutableRef s f a) Source # | |
Defined in Data.Mutable.Internal Methods compare :: GMutableRef s f a -> GMutableRef s f a -> Ordering # (<) :: GMutableRef s f a -> GMutableRef s f a -> Bool # (<=) :: GMutableRef s f a -> GMutableRef s f a -> Bool # (>) :: GMutableRef s f a -> GMutableRef s f a -> Bool # (>=) :: GMutableRef s f a -> GMutableRef s f a -> Bool # max :: GMutableRef s f a -> GMutableRef s f a -> GMutableRef s f a # min :: GMutableRef s f a -> GMutableRef s f a -> GMutableRef s f a # |
Instances
Eq (Ref s (f a)) => Eq (RecRef s f a) Source # | |
Ord (Ref s (f a)) => Ord (RecRef s f a) Source # | |
Defined in Data.Mutable.Instances |
data HListRef :: Type -> [Type] -> Type where Source #
The mutable reference of the HList
type from generic-lens.
The Ref
for ()
(unit). This breaks the pattern for tuple
instances (type
), but is
necessary for type inference (see documentation for Ref
s (a, b) = (Ref
s a, Ref
s b)Ref
).
Since: 0.2.0.0
Constructors
UnitRef |
Instances
Monad (UnitRef :: Type -> Type) Source # | |
Functor (UnitRef :: Type -> Type) Source # | |
Applicative (UnitRef :: Type -> Type) Source # | |
Foldable (UnitRef :: Type -> Type) Source # | |
Defined in Data.Mutable.Instances Methods fold :: Monoid m => UnitRef m -> m # foldMap :: Monoid m => (a -> m) -> UnitRef a -> m # foldMap' :: Monoid m => (a -> m) -> UnitRef a -> m # foldr :: (a -> b -> b) -> b -> UnitRef a -> b # foldr' :: (a -> b -> b) -> b -> UnitRef a -> b # foldl :: (b -> a -> b) -> b -> UnitRef a -> b # foldl' :: (b -> a -> b) -> b -> UnitRef a -> b # foldr1 :: (a -> a -> a) -> UnitRef a -> a # foldl1 :: (a -> a -> a) -> UnitRef a -> a # elem :: Eq a => a -> UnitRef a -> Bool # maximum :: Ord a => UnitRef a -> a # minimum :: Ord a => UnitRef a -> a # | |
Traversable (UnitRef :: Type -> Type) Source # | |
Eq (UnitRef s) Source # | |
Ord (UnitRef s) Source # | |
Read (UnitRef s) Source # | |
Show (UnitRef s) Source # | |
Instances
Functor (VoidRef :: Type -> Type) Source # | |
Foldable (VoidRef :: Type -> Type) Source # | |
Defined in Data.Mutable.Instances Methods fold :: Monoid m => VoidRef m -> m # foldMap :: Monoid m => (a -> m) -> VoidRef a -> m # foldMap' :: Monoid m => (a -> m) -> VoidRef a -> m # foldr :: (a -> b -> b) -> b -> VoidRef a -> b # foldr' :: (a -> b -> b) -> b -> VoidRef a -> b # foldl :: (b -> a -> b) -> b -> VoidRef a -> b # foldl' :: (b -> a -> b) -> b -> VoidRef a -> b # foldr1 :: (a -> a -> a) -> VoidRef a -> a # foldl1 :: (a -> a -> a) -> VoidRef a -> a # elem :: Eq a => a -> VoidRef a -> Bool # maximum :: Ord a => VoidRef a -> a # minimum :: Ord a => VoidRef a -> a # | |
Traversable (VoidRef :: Type -> Type) Source # | |
Eq (VoidRef s) Source # | |
Ord (VoidRef s) Source # | |
Read (VoidRef s) Source # | |
Show (VoidRef s) Source # | |
Providing/overriding instances
Newtype wrapper that can provide any type with a Mutable
instance,
giving it a "non-piecewise" instance. Can be useful for avoiding orphan
instances yet still utilizing auto-deriving features, or for overwriting
the Mutable
instance of other instances.
For example, let's say you want to auto-derive an instance for your data type:
data MyType = MT Int Double OtherType deriving Generic
This is possible if all of MyType
s fields have Mutable
instances.
However, let's say OtherType
comes from an external library that you
don't have control over, and so you cannot give it a Mutable
instance
without incurring an orphan instance.
One solution is to wrap it in VarMut
:
data MyType = MT Int Double (VarMut
OtherType)
deriving Generic
This can then be auto-derived:
instance Mutable s MyType where type Ref s MyType = GRef s MyType
It can also be used to override a Mutable
instance. For example,
even if the Mutable
instance of SomeType
is piecewise-mutable, the
Mutable
instance of
will be not be piecewise.VarMut
SomeType
For example, the Mutable
instance for String
is a mutable linked
list, but it might be more efficient to treat it as an atomic value to
update all at once. You can use
to get that
VarMut
String
Mutable
instance.
Instances
Mutable s (VarMut a) Source # | |
Defined in Data.Mutable.Class Methods thawRef :: (PrimMonad m, PrimState m ~ s) => VarMut a -> m (Ref s (VarMut a)) Source # freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (VarMut a) -> m (VarMut a) Source # copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (VarMut a) -> VarMut a -> m () Source # moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (VarMut a) -> Ref s (VarMut a) -> m () Source # cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (VarMut a) -> m (Ref s (VarMut a)) Source # unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => VarMut a -> m (Ref s (VarMut a)) Source # unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (VarMut a) -> m (VarMut a) Source # | |
IsoHKD VarMut (a :: Type) Source # | Use a |
type Ref s (VarMut a) Source # | |
Defined in Data.Mutable.Class | |
type HKD VarMut (a :: Type) Source # | |
Defined in Data.Mutable.Class |
newtype CoerceMut s a Source #
Similar to VarMut
, this allows you to overwrite the normal Mutable
instance of a type to utilize a coercible type's Mutable
instance
instead of its normal instance. It's also useful to provide an instance for
an externally defined type without incurring orphan instances.
For example, if an external library provides
newtype DoubleVec = DV (Vector Double)
and you want to use it following Vector
s Mutable
instance (via
MVector
), but you don't want to write an orphan instance like
instance Mutable s DoubleVec where typeRef
s DoubleVec =CoerceRef
s DoubleVec (Vector Double)
then you can instead use
as the
data type. This wrapped type does use the inderlying CoerceMut
DoubleVec (Vector Double)Mutable
insatnce for Vector
.
Constructors
CoerceMut | |
Fields
|
Instances
newtype TraverseMut f a Source #
Similar to VarMut
, this allows you to overwrite the normal Mutable
instance for a type to utilize its Traversable
instance instead of its
normal instance. It's also useful to provide an instance for an
externally defined type without incurring orphan instances.
For example, the instance of
is
a normal list of mutable references, instead of a full-on mutable linked
list.Mutable
(TraverseMut
[] a)
Constructors
TraverseMut | |
Fields
|
Instances
newtype Immutable s a Source #
Similar to VarMut
, this allows you to overwrite the normal Mutable
instance of a type to make it immutable.
For example, let's say you have a type, with the automatically derived
generic instance of Mutable
:
data MyType = MT { mtX :: Int , mtY :: Vector Double , mtZ :: String } deriving Generic instance Mutable s MyType where type Ref s MyType = GRef s MyType
This basically uses three mutable references: the Int
, the
, and the Vector
DoubleString
. However, you might want the Mutable
instance of MyType
to be immutable String
field, and so it cannot
be updated at all even when thawed. To do that, you can instead have:
data MyType = MT
{ mtX :: Int
, mtY :: Vector Double
, mtZ :: Immutable
String
}
deriving Generic
instance Mutable s MyType where
type Ref s MyType = GRef s MyType
which has that behavior. The Int
and the Vector
will be mutable
within
, but not the Ref
s MyTypeString
.
Constructors
Immutable | |
Fields
|
Instances
Parts
newtype MutPart s b a Source #
A
is a way to "zoom into" an MutPart
s b aa
, as a part of
a mutable reference on b
. This allows you to only modify a single
a
part of the b
, without touching the rest. It's spiritually
similar to a Lens' b a
.
If MutBranch
is for sum types, then MutPart
is
for product types.
See https://mutable.jle.im/05-mutable-parts.html for an introduction to this type.
An example that is commonly found in the ecosystem is something like
(flipped) write :: Int ->
from
Data.Vector.Mutable --- MVector
s a -> a -> m ()write 3 ::
, for instance, lets you modify a specific part of the vector
without touching the rest.MVector
s a -> a ->
m ()
You would use a MutPart
using freezePart
, copyPart
,
modifyPart
, etc.
For non-composite types, there won't really be any meaningful values. However, we have them for many composite types. For example, for tuples:
mutFst
::MutPart
s (a, b) amutSnd
:: MutPart s (a, b) b
ghci> r <-thawRef
(2, 4) ghci>copyPart
mutFst r 100 ghci>freezeRef
r (100, 4)
If you are using GRef
as an automatically-defined mutable reference,
then the easiest way to create these for your mutable types are with
fieldMut
and posMut
.
If you are using the "Higher-kinded data" pattern, then there's an easy
way to generate a MutPart
for every single field, if you have
a product type --- see hkdMutParts
for more information.
Constructors
MutPart | |
Fields
|
Instances
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z (K1 i (RefFor s c) :: k -> Type) (K1 i (MutPart s (z Identity) c) :: k -> Type) Source # | |
Defined in Data.Mutable.Parts | |
Category (MutPart s :: Type -> Type -> Type) Source # | |
IsoHKD (MutPart s b :: Type -> Type) (a :: Type) Source # | |
type HKD (MutPart s b :: Type -> Type) (a :: Type) Source # | |
freezePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> m a Source #
copyPart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> a -> m () Source #
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutPart s b a | |
-> Ref s b | bigger type (destination) |
-> Ref s a | smaller type (source) |
-> m () |
With a MutPart
, copy a Ref
containing a subvalue into a specific
part of a larger Ref
.
data MyType = MT { mtInt :: Int, mtDouble :: Double } deriving Generic instance Mutable s MyType where type Ref s MyType = GRef s MyType
ghci> x <- thawRef $ MyType 3 4.5 ghci> y <- thawRef $ 100 ghci> movePartInto (fieldMut #mtInt) x y ghci> freezeRef x MyType 100 4.5
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutPart s b a | |
-> Ref s a | smaller type (destination) |
-> Ref s b | bigger type (source) |
-> m () |
With a MutPart
, copy a specific part of a larger Ref
into a Ref
of the smaller subvalue value.
data MyType = MT { mtInt :: Int, mtDouble :: Double } deriving Generic instance Mutable s MyType where type Ref s MyType = GRef s MyType
ghci> x <- thawRef $ MyType 3 4.5 ghci> y <- thawRef $ 100 ghci> movePartOver (fieldMut #mtInt) y x ghci> freezeRef y 3
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutPart s b a | |
-> Ref s b | destination |
-> Ref s b | source |
-> m () |
With a MutPart
, copy a specific part of a large Ref
into that
same part in another large Ref
.
data MyType = MT { mtInt :: Int, mtDouble :: Double } deriving Generic instance Mutable s MyType where type Ref s MyType = GRef s MyType
ghci> x <- thawRef $ MyType 3 4.5 ghci> y <- thawRef $ MyType 100 12.34 ghci> movePartWithin (fieldMut #mtInt) x y ghci> freezeRef x MyType 100 4.5
clonePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> m (Ref s a) Source #
Clone out a subvalue of a larger Ref
.
unsafeFreezePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> m a Source #
A non-copying version of unsafeFreezeRef
that can be more efficient for
types where the mutable representation is the same as the immutable
one (like Vector
).
This is safe as long as you never again modify the mutable reference, since it can potentially directly mutate the frozen value magically.
modifyPart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> a) -> m () Source #
modifyPart' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> a) -> m () Source #
modifyPart
, but forces the result before storing it back in the
reference.
updatePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> (a, r)) -> m r Source #
updatePart' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> (a, r)) -> m r Source #
updatePart
, but forces the result before storing it back in the
reference.
Built-in MutPart
Field
class (Mutable s b, Mutable s a) => FieldMut (fld :: Symbol) s b a | fld b -> a where Source #
Create a MutPart
for a field name. Should work for any type with
one constructor whose mutable reference is GRef
. See fieldMut
for
usage directions.
Mostly leverages the power of Data.Generics.Product.Fields.
Methods
Create a MutPart
for a field name. Should work for any type with
one constructor whose mutable reference is GRef
.
Is meant to be used with OverloadedLabels:
data MyType = MyType { mtInt :: Int, mtDouble :: Double }
deriving (Generic, Show)
instance Mutable s MyType where
type Ref s MyType = GRef
s MyType
ghci> r <-thawRef
(MyType 3 4.5) ghci>freezePart
(fieldMut
#mtInt) r 3 ghci>copyPart
(fieldMut #mtDouble) 1.23 ghci>freezeRef
r MyType 3 1.23
However, you can use it without OverloadedLabels by using Label
with
TypeApplications:
ghci>freezePart
(fieldMut
(Label
@"mtInt")) r 3
This and posMut
are the main ways to generate a MutPart
for
a type whose mutable reference is GRef
. Note that because all of
the lookups are done at compile-time, fieldMut
and posMut
have
more or less identical performance characteristics.
Arguments
:: forall fld s b a. FieldMut fld s b a | |
=> Label fld | field label (usually given using OverloadedLabels, @#blah) |
-> Ref s b | Larger record reference |
-> Ref s a | Internal mutable field |
A helpful wrapper around
. Directly
use a getMutPart
(fieldMut
#blah)fieldMut
to access a mutable field.
Proxy for label type
Constructors
Label |
Position
class (Mutable s b, Mutable s a) => PosMut (i :: Nat) s b a | i b -> a where Source #
Create a MutPart
for a position in a product type. Should work for any
type with one constructor whose mutable reference is GRef
. See
posMut
for usage directions.
Mostly leverages the power of Data.Generics.Product.Positions.
Methods
posMut :: MutPart s b a Source #
Create a MutPart
for a position in a product type. Should work for any
type with one constructor whose mutable reference is GRef
.
Meant to be used with TypeApplications:
data MyType = MyType Int Double
deriving (Generic, Show)
instance Mutable s MyType where
type Ref s MyType = GRef
s MyType
ghci> r <-thawRef
(MyType 3 4.5) ghci>freezePart
(posMut
@1) r 3 ghci>copyPart
(posMut @2) 1.23 ghci>freezeRef
r MyType 3 1.23
This and fieldMut
are the main ways to generate a MutPart
for
a type whose mutable reference is GRef
. Note that because all of
the lookups are done at compile-time, posMut
and fieldMut
have
more or less identical performance characteristics.
Instances
Arguments
:: forall i s b a. PosMut i s b a | |
=> Ref s b | Larger record reference |
-> Ref s a | Internal mutable field |
A helpful wrapper around
. Directly
use a getMutPart
(posMut
@n)posMut
to access a mutable field.
Tuple
class (Mutable s b, Mutable s a) => TupleMut s b a | b -> a where Source #
Create a MutPart
splitting out a product type into a tuple of refs
for every field in that product type. Should work for any type with one
constructor whose mutable reference is GRef
. See tupleMut
for usage
directions.
Mostly leverages the power of Data.Generics.Product.HList.
Methods
tupleMut :: MutPart s b a Source #
Create a MutPart
splitting out a product type into a tuple of refs
for every field in that product type. Should work for any type with one
constructor whose mutable reference is GRef
.
Probably most easily used using withTuple
:
data MyType = MyType Int Double
deriving (Generic, Show)
instance Mutable s MyType where
type Ref s MyType = GRef
s MyType
Now there is an instance of
.TupleMut
m MyType (Int, Double)
ghci> r <-thawRef
(MyType 3 4.5) ghci>withTuple
r $ (rI, rD) -> do ..modifyRef
rI negate .. modifyRef rD (* 2) ghci>freezeRef
r MyType (-3) 9
As can be seen, within the lambda, we can get access to every
mutable reference inside a MyType
reference.
Performance-wise, this appears to be faster than fieldMut
and
posMut
when using a single reference, but slower if using all
references.
Arguments
:: TupleMut s b a | |
=> Ref s b | Larger record reference |
-> (Ref s a -> m r) | What to do with each mutable field. The
|
-> m r |
A helpful wrapper over
. Directly operate on
the items in the data type, getting the references as a tuple. See
withPart
tupleMut
tupleMut
for more details on when this should work.
data MyType = MyType Int Double
deriving (Generic, Show)
instance Mutable s MyType where
type Ref s MyType = GRef
s MyType
ghci> r <-thawRef
(MyType 3 4.5) ghci>withTuple
r $ (rI, rD) -> do ..modifyRef
rI negate .. modifyRef rD (* 2) ghci>freezeRef
r MyType (-3) 9
Higher-Kinded Data
hkdMutParts :: forall z s. (Generic (z (RefFor s)), Generic (z (MutPart s (z Identity))), HKDMutParts s z (Rep (z (RefFor s))) (Rep (z (MutPart s (z Identity))))) => z (MutPart s (z Identity)) Source #
If you are using the "higher-kinded data" pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/, and you
have the appropriate instance for Ref
, then you can use this to
generate a MutPart
for every field, if you have a type with only one
constructor.
data MyTypeF f = MT { mtInt :: f Int , mtDouble :: f Double } deriving Generic instance Mutable (MyTypeFIdentity
) where type Ref (MyTypeFIdentity
) = MyTypeF (RefFor
m) mx :: MutPart s (MyTypeF Identity) (Vector
Int) my :: MutPart s (MyTypeF Identity) (Vector Double) MT mx my = hkdMutParts @MyTypeF
ghci> r <- thawRef (MT 3 4.5) ghci>freezePart
mx r 3 ghci>copyPart
(mtDouble (hkdMutParts @MyTypeF)) r 12.3 ghci>freezeRef
r MT 3 12.3
Performance-wise, this is about equivalent to fieldMut
and posMut
for the most part, so the main advantage would be purely syntactical. If
performance is an issue, you should benchmark all the different ways
just to be sure. As a general rule, it seems like deep nested accesses
are faster with composition of fieldMut
and posMut
, but immediate
shallow access is often faster with hkdMutParts
...but this probably
does vary on a case-by-case basis.
class (Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z i o Source #
Typeclass used to implement hkdMutParts
. See documentation of
hkdMutParts
for more information.
Minimal complete definition
hkdMutParts_
Instances
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s), TypeError ('Text "Cannot use hkdMutParts for uninhabited types: " :<>: 'ShowType z) :: Constraint) => HKDMutParts s z (V1 :: k -> Type) (V1 :: k -> Type) Source # | |
Defined in Data.Mutable.Parts Methods hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> V1 a) -> V1 a | |
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z (U1 :: k -> Type) (U1 :: k -> Type) Source # | |
Defined in Data.Mutable.Parts Methods hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> U1 a) -> U1 a | |
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s), TypeError ('Text "Cannot use hkdMutParts for sum types: " :<>: 'ShowType z) :: Constraint) => HKDMutParts s z (i :+: i' :: k -> Type) (o :: k -> Type) Source # | |
Defined in Data.Mutable.Parts Methods hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> (i :+: i') a) -> o a | |
(HKDMutParts s z i o, HKDMutParts s z i' o') => HKDMutParts s z (i :*: i' :: k -> Type) (o :*: o' :: k -> Type) Source # | |
Defined in Data.Mutable.Parts Methods hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> (i :*: i') a) -> (o :*: o') a | |
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z (K1 i (RefFor s c) :: k -> Type) (K1 i (MutPart s (z Identity) c) :: k -> Type) Source # | |
Defined in Data.Mutable.Parts | |
HKDMutParts s z i o => HKDMutParts s z (M1 a b i :: k -> Type) (M1 a b o :: k -> Type) Source # | |
Defined in Data.Mutable.Parts Methods hkdMutParts_ :: forall (a0 :: k0). (z (RefFor s) -> M1 a b i a0) -> M1 a b o a0 |
Other
mutRec :: forall a as f rec s. (Ref s (rec f as) ~ rec (RecRef s f) as, RecElem rec a a as as (RIndex a as), RecElemFCtx rec (RecRef s f)) => MutPart s (rec f as) (f a) Source #
A MutPart
for a field in a vinyl Rec
, automatically
generated as the first field with a matching type. This is polymorphic
to work over both Rec
and ARec
.
ghci> r <-thawRef
$ [1,2,3]:&
[True, False] :&RNil
ghci> modifyPart (mutRec @Bool) r reverse ghci> freezeRef r [1,2,3] :& [False, True] :& RNil
withCoerceRef :: CoerceRef s b a -> (Ref s a -> m r) -> m r Source #
Handy wrapper over
.getMutPart
coerceRef
Branches
A
represents the information that MutBranch
s b ab
could
potentially be an a
. Similar in spirit to a Prism' b a
.
means that MutBranch
s b aa
is one potential option that b
could be in, or that b
is a sum type and a
is one of the
branches/constructors.
See https://mutable.jle.im/06-mutable-branches.html for an introduction to this module.
If MutPart
is for product types, then MutBranch
is for sum types.
In this case, "branch" means "potential option". For example, the
branches of Either
are Left
and Right
.
The simplest way to make these is by using constrMB
. For instance, to
get the two branches of an Either
:
constrMB #_Left :: MutBranch s (Either a b) a constrMB #_Right :: MutBranch s (Either a b) b
ghci> r <-thawRef
(Left 10) ghci>freezeBranch
(constrMB
#_Left) r Just 10 ghci> freezeBranch (constrMB #_Right) r Nothing
It uses OverloadedLabels, but requires an underscore before the constructor name due to limitations in the extension.
One nice way to use these is with withBranch_
:
ghci> r <-thawRef
(Just 10) ghci>withBranch_
(constrMB #_Just) $ i -> --i
is an Int ref .. modifyRef i (+ 1) ghci>freezeRef
r Just 11
ghci> r <- thawRef Nothing
ghci> withBranch_ (constrMB #_Just) $ i -> -- i
is an Int ref
.. modifyRef i (+ 1)
ghci> freezeRef r
Nothing
Perhaps the most useful usage of this abstraction is for recursive data types.
data List a = Nil | Cons a (List a) deriving Generic instance Mutable s a =>Mutable
s (List a) where type Ref s (List a) =GRef
s (List a)
is now a mutable linked list! Once we make the
GRef
s (List a)MutBranch
for the nil and cons cases:
nilBranch :: MutBranch s (List a) () nilBranch = constrMB #_Nil consBranch :: MutBranch s (List a) (a, List a) consBranch = constrMB #_Cons
Here is a function to check if a linked list is currently empty:
isEmpty :: (PrimMonad m, Mutable s a) => Ref s (List a) -> m Bool isEmpty = hasBranch nilBranch
Here is one to "pop" a mutable linked list, giving us the first value and shifting the rest of the list up.
popStack :: (PrimMonad m, Mutable s a) => Ref s (List a) -> m (Maybe a) popStack r = do c <- projectBranch consBranch r case c of Nothing -> pure Nothing Just (x, xs) -> do moveRef r xs Just $ freezeRef x
And here is a function to concatenate a second linked list to the end of a first one.
concatLists :: (PrimMonad m, Mutable s a) => Ref s (List a) -> Ref s (List a) -> m () concatLists l1 l2 = do c <- projectBranch consBranch l1 case c of Nothing -> moveRef l1 l2 Just (_, xs) -> concatLists xs l2
Constructors
MutBranch | |
Fields
|
thawBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> a -> m (Ref s b) Source #
With a MutBranch
, thaw an a
into a mutable s
on that branch.
ghci> r <-thawBranch
(constrMB
#_Left) 10 ghci>freezeRef
r Left 10
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if is |
-> Ref s b | Structure to read out of |
-> m (Maybe a) |
With a MutBranch
, read out a specific a
branch of an s
, if it exists.
ghci> r <-thawRef
(Left 10) ghci>freezeBranch
(constrMB
#_Left) r Just 10 ghci> freezeBranch (constrMB #_Right) r Nothing
moveBranch :: (Mutable s b, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> Ref s a -> m () Source #
With a MutBranch
, overwrite an s
as an a
, on that branch.
ghci> r <- thawRef (Left 10) ghci> s <- thawRef 100 ghci> moveBranch (constrMB #_Left) r s ghci> freezeRef r Left 100 ghci> t <- thawRef True ghci> moveBranch (constrMB #_Right) r t ghci> freezeRef r Right True
Arguments
:: (Mutable s b, Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if |
-> Ref s b | Structure to write into |
-> a | Value to set |
-> m () |
With a MutBranch
, set s
to have the branch a
.
ghci> r <-thawRef
(Left 10) ghci>copyBranch
(constrMB
#_Left) r 5678 ghci>freezeRef
r Left 5678 ghci> copyBranch (constrMB #_Right) r True ghci> freezeRef r Right True
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if |
-> Ref s b | Structure to read out of |
-> m (Maybe (Ref s a)) |
With a MutBranch
, attempt to clone out a branch of a mutable
s
, if possible.
ghci> r <- thawRef (Left 10) ghci> s <- cloneBranch (constrMB #_Left) ghci> case s of Just s' -> freezeRef s' 10
ghci> r <- thawRef (Right True) ghci> s <- cloneBranch (constrMB #_Left) ghci> case s of Nothing -> "it was Right" "it was Right"
hasBranch :: (PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m Bool Source #
Check if an s
is currently a certain branch a
.
hasn'tBranch :: (PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m Bool Source #
Check if an s
is not currently a certain branch a
.
unsafeThawBranch :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutBranch s b a -> a -> m (Ref s b) Source #
A non-copying version of thawBranch
that can be more efficient for
types where the mutable representation is the same as the immutable one
(like Vector
).
This is safe as long as you never again use the original pure value, since it can potentially directly mutate it.
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if is |
-> Ref s b | Structure to read out of |
-> m (Maybe a) |
A non-copying version of freezeBranch
that can be more efficient
for types where the mutable representation is the same as the immutable
one (like Vector
).
This is safe as long as you never again modify the mutable reference, since it can potentially directly mutate the frozen value magically.
Arguments
:: (PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if is |
-> Ref s b | Structure to read out of and write into |
-> (Ref s a -> m r) | Action to perform on the |
-> m (Maybe r) |
With a MutBranch
, if an s
is on the a
branch, perform an action
on the a
reference and overwrite the s
with the modified a
.
Returns the result of the action, if a
was found.
ghci> r <-thawRef
(Just 10) ghci>withBranch_
(constrMB
#_Just) $ i -> --i
is an Int ref ..modifyRef
i (+ 1) ghci>freezeRef
r Just 11
ghci> r <- thawRef Nothing
ghci> withBranch_ (constrMB #_Just) $ i -> -- i
is an Int ref
.. modifyRef i (+ 1)
ghci> freezeRef r
Nothing
Arguments
:: (PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if is |
-> Ref s b | Structure to read out of and write into |
-> (Ref s a -> m r) | Action to perform on the |
-> m () |
withBranch
, but discarding the returned value.
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if |
-> Ref s b | Structure to read out of and write into |
-> (a -> a) | Pure function modifying |
-> m () |
With a MutBranch
, run a pure function over a potential branch a
of
s
. If s
is not on that branch, leaves s
unchanged.
ghci> r <-thawRef
(Just 10) ghci>modifyBranch
(constrMB
#_Just) r (+ 1) ghci> freezeRef r Just 11
ghci> r <- thawRef Nothing ghci> modifyBranch (constrMB #_Just) r (+ 1) ghci> freezeRef r Nothing
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if |
-> Ref s b | Structure to read out of and write into |
-> (a -> a) | Pure function modifying |
-> m () |
modifyBranch
, but forces the result before storing it back in the
reference.
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if |
-> Ref s b | Structure to read out of and write into |
-> (a -> (a, r)) | |
-> m (Maybe r) |
With a MutBranch
, run a pure function over a potential branch a
of
s
. The function returns the updated a
and also an output value to
observe. If s
is not on that branch, leaves s
unchanged.
ghci> r <-thawRef
(Just 10) ghci>updateBranch
(constrMB
#_Just) r $ i -> (i + 1, show i) Just "10" ghci>freezeRef
r Just 11
ghci> r <- thawRef Nothing ghci> updateBranch (constrMB #_Just) r $ i -> (i + 1, show i) Nothing ghci> freezeRef r Nothing
Arguments
:: (Mutable s a, PrimMonad m, PrimState m ~ s) | |
=> MutBranch s b a | How to check if |
-> Ref s b | Structure to read out of and write into |
-> (a -> (a, r)) | |
-> m (Maybe r) |
updateBranch
, but forces the result before storing it back in the
reference.
Built-in MutBranch
Using GHC Generics
constrMB :: forall ctor s b a. (Ref s b ~ GRef s b, GMutBranchConstructor ctor s (Rep b) a) => CLabel ctor -> MutBranch s b a Source #
Create a MutBranch
for any data type with a Generic
instance by
specifying the constructor name using OverloadedLabels
ghci> r <-thawRef
(Left 10) ghci>freezeBranch
(constrMB
#_Left) r Just 10 ghci> freezeBranch (constrMB #_Right) r Nothing
Note that due to limitations in OverloadedLabels, you must prefix the constructor name with an undescore.
There also isn't currently any way to utilize OverloadedLabels with
operator identifiers, so using it with operator constructors (like :
and []
) requires explicit TypeApplications:
-- |MutBranch
focusing on the cons case of a list consMB :: (PrimMonad m, Mutable s a) => MutBranch s [a] (a, [a]) consMB =constrMB
(CLabel
@":")
data CLabel (ctor :: Symbol) Source #
A version of Label
that removes an underscore at
the beginning when used with -XOverloadedLabels. Used to specify
constructors, since labels are currently not able to start with capital
letters.
Constructors
CLabel |
Instances
ctor_ ~ AppendSymbol "_" ctor => IsLabel ctor_ (CLabel ctor) Source # | |
Defined in Data.Mutable.Branches |
class (GMutable s f, Mutable s a) => GMutBranchConstructor (ctor :: Symbol) s f a | ctor f -> a Source #
Typeclass powering constrMB
using GHC Generics.
Heavily inspired by Data.Generics.Sum.Constructors.
Minimal complete definition
gmbcProj, gmbcEmbed
Instances
(Mutable s a, GMutBranchSum ctor (HasCtorP ctor l) s l r a) => GMutBranchConstructor ctor s (l :+: r) a Source # | |
GMutBranchConstructor ctor m f a => GMutBranchConstructor ctor m (M1 D meta f) a Source # | |
(GMutable s f, Mutable s a, GIsList (GRef_ s f) (GRef_ s f) (MapRef s as) (MapRef s as), GIsList f f as as, ListTuple a a as as, ListRefTuple s b as, Ref s a ~ b) => GMutBranchConstructor ctor s (M1 C ('MetaCons ctor fixity fields) f) a Source # | |
type family MapRef s as where ... Source #
Useful type family to
over every item in a type-level listRef
m
ghci> :kind! MapRef IO '[Int, V.Vector Double] '[ MutVar RealWorld Int, MVector RealWorld Double ]
For common types
consMB :: Mutable s a => MutBranch s [a] (a, [a]) Source #
MutBranch
focusing on the cons case of a list
Re-exports
class Monad m => PrimMonad (m :: Type -> Type) #
Class of monads which can perform primitive state-transformer actions
Minimal complete definition
Instances
PrimMonad IO | |
PrimMonad (ST s) | |
PrimMonad (ST s) | |
PrimMonad m => PrimMonad (MaybeT m) | |
PrimMonad m => PrimMonad (ListT m) | |
PrimMonad m => PrimMonad (IdentityT m) | |
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) | |
(Monoid w, PrimMonad m) => PrimMonad (AccumT w m) | Since: primitive-0.6.3.0 |
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) | |
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) | |
PrimMonad m => PrimMonad (StateT s m) | |
PrimMonad m => PrimMonad (StateT s m) | |
PrimMonad m => PrimMonad (SelectT r m) | |
PrimMonad m => PrimMonad (ReaderT r m) | |
PrimMonad m => PrimMonad (ExceptT e m) | |
(Error e, PrimMonad m) => PrimMonad (ErrorT e m) | |
PrimMonad m => PrimMonad (ContT r m) | Since: primitive-0.6.3.0 |
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) | |
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) | |
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) | |
type family PrimState (m :: Type -> Type) #
State token type