| Copyright | (c) Justin Le 2020 |
|---|---|
| License | BSD3 |
| Maintainer | justin@jle.im |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Mutable.Instances
Description
Exports Ref data types for various common data types, and also the
tools for automatic derivation of instances. See Data.Mutable for
more information.
Synopsis
- newtype RecRef s f a = RecRef {}
- data HListRef :: Type -> [Type] -> Type where
- data UnitRef s = UnitRef
- data VoidRef s
- newtype GRef s a = GRef {}
- gThawRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => a -> m (GRef s a)
- gFreezeRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m a
- gCopyRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> a -> m ()
- gMoveRef :: (GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> GRef s a -> m ()
- gCloneRef :: (GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m (GRef s a)
- gUnsafeThawRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => a -> m (GRef s a)
- gUnsafeFreezeRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m a
- class GMutable s (f :: Type -> Type) where
- thawHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s))
- freezeHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity)
- copyHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z Identity -> m ()
- moveHKD :: forall z m s. (Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z (RefFor s) -> m ()
- cloneHKD :: forall z m s. (Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z (RefFor s))
- unsafeThawHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s))
- unsafeFreezeHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity)
- newtype CoerceRef s b a = CoerceRef {
- getCoerceRef :: Ref s a
- thawCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => b -> m (CoerceRef s b a)
- freezeCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m b
- copyCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> b -> m ()
- moveCoerce :: (Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> CoerceRef s b a -> m ()
- cloneCoerce :: (Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m (CoerceRef s b a)
- unsafeThawCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => b -> m (CoerceRef s b a)
- unsafeFreezeCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m b
- newtype TraverseRef s f a = TraverseRef {
- getTraverseRef :: f (Ref s a)
- thawTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => f a -> m (TraverseRef s f a)
- freezeTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (f a)
- copyTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> f a -> m ()
- moveTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> TraverseRef s f a -> m ()
- cloneTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (TraverseRef s f a)
- unsafeThawTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => f a -> m (TraverseRef s f a)
- unsafeFreezeTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (f a)
- newtype ImmutableRef s a = ImmutableRef {
- getImmutableRef :: a
- thawImmutable :: Applicative m => a -> m (ImmutableRef s a)
- freezeImmutable :: Applicative m => ImmutableRef s a -> m a
- copyImmutable :: Applicative m => ImmutableRef s a -> a -> m ()
- newtype GMutableRef s f a = GMutableRef {
- getGMutableRef :: GRef_ s f a
- newtype MutSumF s f g a = MutSumF {
- getMutSumF :: MutVar s ((f :+: g) a)
- type family MapRef s as where ...
Documentation
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 # | |
Generic
Automatically generate a piecewise mutable reference for any Generic
instance.
-- | anyGenericinstance data MyType = MyType { mtInt :: Int, mtDouble :: Double } deriving (Generic, Show) instance Mutable s MyType where type Ref s MyType =GRefs MyType
ghci> r <-thawRef(MyType 3 4.5) ghci>freezeRefr 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 | |
gThawRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => a -> m (GRef s a) Source #
gFreezeRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m a Source #
gCopyRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> a -> m () Source #
gMoveRef :: (GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> GRef s a -> m () Source #
gCloneRef :: (GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m (GRef s a) Source #
gUnsafeThawRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => a -> m (GRef s a) Source #
Default unsafeThawRef for GRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with GRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the GRef s aRef class. See documentation
for GRef for more information.
gUnsafeFreezeRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m a Source #
Default unsafeFreezeRef for GRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with GRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the GRef s aRef class. See documentation
for GRef for more information.
class GMutable s (f :: Type -> Type) Source #
Minimal complete definition
gThawRef_, gFreezeRef_, gCopyRef_, gMoveRef_, gCloneRef_, gUnsafeThawRef_, gUnsafeFreezeRef_
Instances
| GMutable s (V1 :: Type -> Type) Source # | |
Defined in Data.Mutable.Internal Methods gThawRef_ :: (PrimMonad m, PrimState m ~ s) => V1 a -> m (GRef_ s V1 a) gFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s V1 a -> m (V1 a) gCopyRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s V1 a -> V1 a -> m () gMoveRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s V1 a -> GRef_ s V1 a -> m () gCloneRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s V1 a -> m (GRef_ s V1 a) gUnsafeThawRef_ :: (PrimMonad m, PrimState m ~ s) => V1 a -> m (GRef_ s V1 a) gUnsafeFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s V1 a -> m (V1 a) | |
| GMutable s (U1 :: Type -> Type) Source # | |
Defined in Data.Mutable.Internal Methods gThawRef_ :: (PrimMonad m, PrimState m ~ s) => U1 a -> m (GRef_ s U1 a) gFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s U1 a -> m (U1 a) gCopyRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s U1 a -> U1 a -> m () gMoveRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s U1 a -> GRef_ s U1 a -> m () gCloneRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s U1 a -> m (GRef_ s U1 a) gUnsafeThawRef_ :: (PrimMonad m, PrimState m ~ s) => U1 a -> m (GRef_ s U1 a) gUnsafeFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s U1 a -> m (U1 a) | |
| (GMutable s f, GMutable s g) => GMutable s (f :+: g) Source # | |
Defined in Data.Mutable.Internal Methods gThawRef_ :: (PrimMonad m, PrimState m ~ s) => (f :+: g) a -> m (GRef_ s (f :+: g) a) gFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :+: g) a -> m ((f :+: g) a) gCopyRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :+: g) a -> (f :+: g) a -> m () gMoveRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :+: g) a -> GRef_ s (f :+: g) a -> m () gCloneRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :+: g) a -> m (GRef_ s (f :+: g) a) gUnsafeThawRef_ :: (PrimMonad m, PrimState m ~ s) => (f :+: g) a -> m (GRef_ s (f :+: g) a) gUnsafeFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :+: g) a -> m ((f :+: g) a) | |
| (GMutable s f, GMutable s g) => GMutable s (f :*: g) Source # | |
Defined in Data.Mutable.Internal Methods gThawRef_ :: (PrimMonad m, PrimState m ~ s) => (f :*: g) a -> m (GRef_ s (f :*: g) a) gFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :*: g) a -> m ((f :*: g) a) gCopyRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :*: g) a -> (f :*: g) a -> m () gMoveRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :*: g) a -> GRef_ s (f :*: g) a -> m () gCloneRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :*: g) a -> m (GRef_ s (f :*: g) a) gUnsafeThawRef_ :: (PrimMonad m, PrimState m ~ s) => (f :*: g) a -> m (GRef_ s (f :*: g) a) gUnsafeFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (f :*: g) a -> m ((f :*: g) a) | |
| Mutable s c => GMutable s (K1 i c :: Type -> Type) Source # | |
Defined in Data.Mutable.Internal Methods gThawRef_ :: (PrimMonad m, PrimState m ~ s) => K1 i c a -> m (GRef_ s (K1 i c) a) gFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (K1 i c) a -> m (K1 i c a) gCopyRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (K1 i c) a -> K1 i c a -> m () gMoveRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (K1 i c) a -> GRef_ s (K1 i c) a -> m () gCloneRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (K1 i c) a -> m (GRef_ s (K1 i c) a) gUnsafeThawRef_ :: (PrimMonad m, PrimState m ~ s) => K1 i c a -> m (GRef_ s (K1 i c) a) gUnsafeFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (K1 i c) a -> m (K1 i c a) | |
| GMutable s f => GMutable s (M1 i c f) Source # | |
Defined in Data.Mutable.Internal Methods gThawRef_ :: (PrimMonad m, PrimState m ~ s) => M1 i c f a -> m (GRef_ s (M1 i c f) a) gFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (M1 i c f) a -> m (M1 i c f a) gCopyRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (M1 i c f) a -> M1 i c f a -> m () gMoveRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (M1 i c f) a -> GRef_ s (M1 i c f) a -> m () gCloneRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (M1 i c f) a -> m (GRef_ s (M1 i c f) a) gUnsafeThawRef_ :: (PrimMonad m, PrimState m ~ s) => M1 i c f a -> m (GRef_ s (M1 i c f) a) gUnsafeFreezeRef_ :: (PrimMonad m, PrimState m ~ s) => GRef_ s (M1 i c f) a -> m (M1 i c f a) | |
Higher-Kinded Data Pattern
thawHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s)) Source #
Default thawRef for the higher-kinded data pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with z ( as the RefFor s)Ref.
However, it can be useful if you are using a z ( just as
a normal data type, independent of the RefFor s)Ref class. See documentation
for Mutable for more information.
freezeHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity) Source #
Default freezeRef for the higher-kinded data pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with z ( as the RefFor s)Ref.
However, it can be useful if you are using a z ( just as
a normal data type, independent of the RefFor s)Ref class. See documentation
for Mutable for more information.
copyHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z Identity -> m () Source #
Default copyRef for the higher-kinded data pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with z ( as the RefFor s)Ref.
However, it can be useful if you are using a z ( just as
a normal data type, independent of the RefFor s)Ref class. See documentation
for Mutable for more information.
moveHKD :: forall z m s. (Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z (RefFor s) -> m () Source #
Default moveRef for the higher-kinded data pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with z ( as the RefFor s)Ref.
However, it can be useful if you are using a z ( just as
a normal data type, independent of the RefFor s)Ref class. See documentation
for Mutable for more information.
cloneHKD :: forall z m s. (Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z (RefFor s)) Source #
Default cloneRef for the higher-kinded data pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with z ( as the RefFor s)Ref.
However, it can be useful if you are using a z ( just as
a normal data type, independent of the RefFor s)Ref class. See documentation
for Mutable for more information.
unsafeThawHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s)) Source #
Default unsafeThawRef for the higher-kinded data pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with z ( as the RefFor s)Ref.
However, it can be useful if you are using a z ( just as
a normal data type, independent of the RefFor s)Ref class. See documentation
for Mutable for more information.
unsafeFreezeHKD :: forall z m s. (Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s)), PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity) Source #
Default unsafeFreezeRef for the higher-kinded data pattern, a la
https://reasonablypolymorphic.com/blog/higher-kinded-data/.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with z ( as the RefFor s)Ref.
However, it can be useful if you are using a z ( just as
a normal data type, independent of the RefFor s)Ref class. See documentation
for Mutable for more information.
Coercible
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 (VectorDouble) instanceMutables MyVec where typeRefs MyVec =CoerceRefs s (VectorDouble)
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
thawCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => b -> m (CoerceRef s b a) Source #
Default thawRef for CoerceRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with CoerceRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the CoerceRef s b aRef class. See documentation
for CoerceRef for more information.
freezeCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m b Source #
Default freezeRef for CoerceRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with CoerceRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the CoerceRef s b aRef class. See documentation
for CoerceRef for more information.
copyCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> b -> m () Source #
Default copyRef for CoerceRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with CoerceRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the CoerceRef s b aRef class. See documentation
for CoerceRef for more information.
moveCoerce :: (Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> CoerceRef s b a -> m () Source #
Default moveRef for CoerceRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with CoerceRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the CoerceRef s b aRef class. See documentation
for CoerceRef for more information.
cloneCoerce :: (Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m (CoerceRef s b a) Source #
Default cloneRef for CoerceRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with CoerceRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the CoerceRef s b aRef class. See documentation
for CoerceRef for more information.
unsafeThawCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => b -> m (CoerceRef s b a) Source #
Default unsafeThawRef for CoerceRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with CoerceRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the CoerceRef s b aRef class. See documentation
for CoerceRef for more information.
unsafeFreezeCoerce :: (Coercible b a, Mutable s a, PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m b Source #
Default unsafeFreezeRef for CoerceRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with CoerceRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the CoerceRef s b aRef class. See documentation
for CoerceRef for more information.
Traversable
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>copyTraverser [0,0,0,0] ghci>freezeTraverser [0,0,0,0,5,6,7,8,9,10] ghci>copyTraverser [20..50] ghci>freezeTraverser [20,21,22,23,24,25,26,27,28,29]
Constructors
| TraverseRef | |
Fields
| |
Instances
thawTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => f a -> m (TraverseRef s f a) Source #
Default thawRef for TraverseRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with TraverseRef as the
Ref. However, it can be useful if you are using a just as a normal data type, independent of the TraverseRef
m f aRef class. See
documentation for TraverseRef for more information.
freezeTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (f a) Source #
Default freezeRef for TraverseRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with TraverseRef as the
Ref. However, it can be useful if you are using a just as a normal data type, independent of the TraverseRef
m f aRef class. See
documentation for TraverseRef for more information.
copyTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> f a -> m () Source #
Default copyRef for TraverseRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with TraverseRef as the
Ref. However, it can be useful if you are using a just as a normal data type, independent of the TraverseRef
m f aRef class. See
documentation for TraverseRef for more information.
Arguments
| :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) | |
| => TraverseRef s f a | destination |
| -> TraverseRef s f a | source |
| -> m () |
Default moveRef for TraverseRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with TraverseRef as the
Ref. However, it can be useful if you are using a just as a normal data type, independent of the TraverseRef
m f aRef class. See
documentation for TraverseRef for more information.
cloneTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (TraverseRef s f a) Source #
Default cloneRef for TraverseRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with TraverseRef as the
Ref. However, it can be useful if you are using a just as a normal data type, independent of the TraverseRef
m f aRef class. See
documentation for TraverseRef for more information.
unsafeThawTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => f a -> m (TraverseRef s f a) Source #
Default unsafeThawRef for TraverseRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with TraverseRef as the
Ref. However, it can be useful if you are using a just as a normal data type, independent of the TraverseRef
m f aRef class. See
documentation for TraverseRef for more information.
unsafeFreezeTraverse :: (Traversable f, Mutable s a, PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (f a) Source #
Default unsafeFreezeRef for TraverseRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with TraverseRef as the
Ref. However, it can be useful if you are using a just as a normal data type, independent of the TraverseRef
m f aRef class. See
documentation for TraverseRef for more information.
Immutable
newtype ImmutableRef s a Source #
A "Ref" that can be used to give a default Mutable instance that
is immutable. Nothing is allocated ever, all attempts to modify it will
be ignored, and freezeRef will just get the original thawed value.
Really only exists to be used with Immutable.
Constructors
| ImmutableRef | |
Fields
| |
Instances
thawImmutable :: Applicative m => a -> m (ImmutableRef s a) Source #
Default thawRef for ImmutableRef.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with ImmutableRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the ImmutableRef s b aRef class. See documentation
for ImmutableRef for more information.
freezeImmutable :: Applicative m => ImmutableRef s a -> m a Source #
Default freezeRef for ImmutableRef. This will always return the
originally thawed value, ignoring all copies and writes.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with ImmutableRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the ImmutableRef s b aRef class. See documentation
for ImmutableRef for more information.
copyImmutable :: Applicative m => ImmutableRef s a -> a -> m () Source #
Default copyRef for ImmutableRef. This is a no-op and does
nothing, since freezing will always return the originally thawed value.
You likely won't ever use this directly, since it is automatically
provided if you have a Mutable instance with ImmutableRef as the Ref.
However, it can be useful if you are using a just as
a normal data type, independent of the ImmutableRef s b aRef class. See documentation
for ImmutableRef for more information.
Instances for Generics combinators themselves
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 # | |
newtype MutSumF s f g a Source #
Wraps :+: in a mutable reference. Used internally to represent
generic sum references.
Constructors
| MutSumF | |
Fields
| |
Utility
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 ]