mutable-0.2.2.0: Automatic piecewise-mutable references for your types
Copyright(c) Justin Le 2020
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

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

Documentation

newtype RecRef s f a Source #

Ref for components in a vinyl Rec.

Constructors

RecRef 

Fields

Instances

Instances details
Eq (Ref s (f a)) => Eq (RecRef s f a) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

(==) :: RecRef s f a -> RecRef s f a -> Bool #

(/=) :: RecRef s f a -> RecRef s f a -> Bool #

Ord (Ref s (f a)) => Ord (RecRef s f a) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

compare :: RecRef s f a -> RecRef s f a -> Ordering #

(<) :: RecRef s f a -> RecRef s f a -> Bool #

(<=) :: RecRef s f a -> RecRef s f a -> Bool #

(>) :: RecRef s f a -> RecRef s f a -> Bool #

(>=) :: RecRef s f a -> RecRef s f a -> Bool #

max :: RecRef s f a -> RecRef s f a -> RecRef s f a #

min :: RecRef s f a -> RecRef s f a -> RecRef s f a #

data HListRef :: Type -> [Type] -> Type where Source #

The mutable reference of the HList type from generic-lens.

Constructors

NilRef :: HListRef s '[] 
(:!>) :: Ref s a -> HListRef s as -> HListRef s (a ': as) infixr 5 

data UnitRef s Source #

The Ref for () (unit). This breaks the pattern for tuple instances (type Ref s (a, b) = (Ref s a, Ref s b)), but is necessary for type inference (see documentation for Ref).

Since: 0.2.0.0

Constructors

UnitRef 

Instances

Instances details
Monad (UnitRef :: Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

(>>=) :: UnitRef a -> (a -> UnitRef b) -> UnitRef b #

(>>) :: UnitRef a -> UnitRef b -> UnitRef b #

return :: a -> UnitRef a #

Functor (UnitRef :: Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

fmap :: (a -> b) -> UnitRef a -> UnitRef b #

(<$) :: a -> UnitRef b -> UnitRef a #

Applicative (UnitRef :: Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

pure :: a -> UnitRef a #

(<*>) :: UnitRef (a -> b) -> UnitRef a -> UnitRef b #

liftA2 :: (a -> b -> c) -> UnitRef a -> UnitRef b -> UnitRef c #

(*>) :: UnitRef a -> UnitRef b -> UnitRef b #

(<*) :: UnitRef a -> UnitRef b -> UnitRef a #

Foldable (UnitRef :: Type -> Type) Source # 
Instance details

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 #

toList :: UnitRef a -> [a] #

null :: UnitRef a -> Bool #

length :: UnitRef a -> Int #

elem :: Eq a => a -> UnitRef a -> Bool #

maximum :: Ord a => UnitRef a -> a #

minimum :: Ord a => UnitRef a -> a #

sum :: Num a => UnitRef a -> a #

product :: Num a => UnitRef a -> a #

Traversable (UnitRef :: Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

traverse :: Applicative f => (a -> f b) -> UnitRef a -> f (UnitRef b) #

sequenceA :: Applicative f => UnitRef (f a) -> f (UnitRef a) #

mapM :: Monad m => (a -> m b) -> UnitRef a -> m (UnitRef b) #

sequence :: Monad m => UnitRef (m a) -> m (UnitRef a) #

Eq (UnitRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

(==) :: UnitRef s -> UnitRef s -> Bool #

(/=) :: UnitRef s -> UnitRef s -> Bool #

Ord (UnitRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

compare :: UnitRef s -> UnitRef s -> Ordering #

(<) :: UnitRef s -> UnitRef s -> Bool #

(<=) :: UnitRef s -> UnitRef s -> Bool #

(>) :: UnitRef s -> UnitRef s -> Bool #

(>=) :: UnitRef s -> UnitRef s -> Bool #

max :: UnitRef s -> UnitRef s -> UnitRef s #

min :: UnitRef s -> UnitRef s -> UnitRef s #

Read (UnitRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Show (UnitRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

showsPrec :: Int -> UnitRef s -> ShowS #

show :: UnitRef s -> String #

showList :: [UnitRef s] -> ShowS #

data VoidRef s Source #

The Ref for Void.

Since: 0.2.0.0

Instances

Instances details
Functor (VoidRef :: Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

fmap :: (a -> b) -> VoidRef a -> VoidRef b #

(<$) :: a -> VoidRef b -> VoidRef a #

Foldable (VoidRef :: Type -> Type) Source # 
Instance details

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 #

toList :: VoidRef a -> [a] #

null :: VoidRef a -> Bool #

length :: VoidRef a -> Int #

elem :: Eq a => a -> VoidRef a -> Bool #

maximum :: Ord a => VoidRef a -> a #

minimum :: Ord a => VoidRef a -> a #

sum :: Num a => VoidRef a -> a #

product :: Num a => VoidRef a -> a #

Traversable (VoidRef :: Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

traverse :: Applicative f => (a -> f b) -> VoidRef a -> f (VoidRef b) #

sequenceA :: Applicative f => VoidRef (f a) -> f (VoidRef a) #

mapM :: Monad m => (a -> m b) -> VoidRef a -> m (VoidRef b) #

sequence :: Monad m => VoidRef (m a) -> m (VoidRef a) #

Eq (VoidRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

(==) :: VoidRef s -> VoidRef s -> Bool #

(/=) :: VoidRef s -> VoidRef s -> Bool #

Ord (VoidRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

compare :: VoidRef s -> VoidRef s -> Ordering #

(<) :: VoidRef s -> VoidRef s -> Bool #

(<=) :: VoidRef s -> VoidRef s -> Bool #

(>) :: VoidRef s -> VoidRef s -> Bool #

(>=) :: VoidRef s -> VoidRef s -> Bool #

max :: VoidRef s -> VoidRef s -> VoidRef s #

min :: VoidRef s -> VoidRef s -> VoidRef s #

Read (VoidRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Show (VoidRef s) Source # 
Instance details

Defined in Data.Mutable.Instances

Methods

showsPrec :: Int -> VoidRef s -> ShowS #

show :: VoidRef s -> String #

showList :: [VoidRef s] -> ShowS #

Generic

newtype GRef s a Source #

Automatically generate a piecewise mutable reference for any Generic instance.

-- | any Generic 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 unGRef @MyType 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.

Constructors

GRef 

Fields

Instances

Instances details
(Generic a, GMutable s (Rep a)) => DefaultMutable s a (GRef s a) Source # 
Instance details

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

Defined in Data.Mutable.Internal

Methods

(==) :: GRef s a -> GRef s a -> Bool #

(/=) :: GRef s a -> GRef s a -> Bool #

Ord (GRef_ s (Rep a) ()) => Ord (GRef s a) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

compare :: GRef s a -> GRef s a -> Ordering #

(<) :: GRef s a -> GRef s a -> Bool #

(<=) :: GRef s a -> GRef s a -> Bool #

(>) :: GRef s a -> GRef s a -> Bool #

(>=) :: GRef s a -> GRef s a -> Bool #

max :: GRef s a -> GRef s a -> GRef s a #

min :: GRef s a -> GRef s a -> GRef s a #

gThawRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => a -> m (GRef s a) Source #

Default thawRef 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 GRef s a just as a normal data type, independent of the Ref class. See documentation for GRef for more information.

gFreezeRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m a Source #

Default freezeRef 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 GRef s a just as a normal data type, independent of the Ref class. See documentation for GRef for more information.

gCopyRef :: (Generic a, GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> a -> m () Source #

Default copyRef 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 GRef s a just as a normal data type, independent of the Ref class. See documentation for GRef for more information.

gMoveRef :: (GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> GRef s a -> m () Source #

Default moveRef 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 GRef s a just as a normal data type, independent of the Ref class. See documentation for GRef for more information.

gCloneRef :: (GMutable s (Rep a), PrimMonad m, PrimState m ~ s) => GRef s a -> m (GRef s a) Source #

Default cloneRef 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 GRef s a just as a normal data type, independent of the Ref class. See documentation for GRef for more information.

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 GRef s a just as a normal data type, independent of the Ref 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 GRef s a just as a normal data type, independent of the Ref class. See documentation for GRef for more information.

class GMutable s (f :: Type -> Type) Source #

Class for automatic generation of Ref for Generic instances. See GRef for more information.

Minimal complete definition

gThawRef_, gFreezeRef_, gCopyRef_, gMoveRef_, gCloneRef_, gUnsafeThawRef_, gUnsafeFreezeRef_

Associated Types

type GRef_ s f = (u :: Type -> Type) | u -> f Source #

Instances

Instances details
GMutable s (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

type GRef_ s V1 = (u :: Type -> Type) Source #

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

Defined in Data.Mutable.Internal

Associated Types

type GRef_ s U1 = (u :: Type -> Type) Source #

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

Defined in Data.Mutable.Internal

Associated Types

type GRef_ s (f :+: g) = (u :: Type -> Type) Source #

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

Defined in Data.Mutable.Internal

Associated Types

type GRef_ s (f :*: g) = (u :: Type -> Type) Source #

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

Defined in Data.Mutable.Internal

Associated Types

type GRef_ s (K1 i c) = (u :: Type -> Type) Source #

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

Defined in Data.Mutable.Internal

Associated Types

type GRef_ s (M1 i c f) = (u :: Type -> Type) Source #

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 (RefFor s) as the Ref. However, it can be useful if you are using a z (RefFor s) just as a normal data type, independent of the 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 (RefFor s) as the Ref. However, it can be useful if you are using a z (RefFor s) just as a normal data type, independent of the 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 (RefFor s) as the Ref. However, it can be useful if you are using a z (RefFor s) just as a normal data type, independent of the 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 (RefFor s) as the Ref. However, it can be useful if you are using a z (RefFor s) just as a normal data type, independent of the 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 (RefFor s) as the Ref. However, it can be useful if you are using a z (RefFor s) just as a normal data type, independent of the 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 (RefFor s) as the Ref. However, it can be useful if you are using a z (RefFor s) just as a normal data type, independent of the 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 (RefFor s) as the Ref. However, it can be useful if you are using a z (RefFor s) just as a normal data type, independent of the 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 (Vector Double)

instance Mutable s MyVec where
    type Ref s MyVec = CoerceRef s s (Vector Double)

The Ref s MyVec uses the a MVector Double under the hood.

It's essentially a special case of GRef for newtypes.

Constructors

CoerceRef 

Fields

Instances

Instances details
(Coercible b a, Mutable s a) => DefaultMutable s b (CoerceRef s b a) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: (PrimMonad m, PrimState m ~ s) => b -> m (CoerceRef s b a) Source #

defaultFreezeRef :: (PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m b Source #

defaultCopyRef :: (PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> b -> m () Source #

defaultMoveRef :: (PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> CoerceRef s b a -> m () Source #

defaultCloneRef :: (PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m (CoerceRef s b a) Source #

defaultUnsafeThawRef :: (PrimMonad m, PrimState m ~ s) => b -> m (CoerceRef s b a) Source #

defaultUnsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => CoerceRef s b a -> m b Source #

IsoHKD (CoerceRef s b :: Type -> Type) (a :: Type) Source #

Use a CoerceRef s b a as if it were a Ref s a

Instance details

Defined in Data.Mutable.Internal

Associated Types

type HKD (CoerceRef s b) a #

Methods

unHKD :: HKD (CoerceRef s b) a -> CoerceRef s b a #

toHKD :: CoerceRef s b a -> HKD (CoerceRef s b) a #

Eq (Ref s a) => Eq (CoerceRef s b a) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

(==) :: CoerceRef s b a -> CoerceRef s b a -> Bool #

(/=) :: CoerceRef s b a -> CoerceRef s b a -> Bool #

Ord (Ref s a) => Ord (CoerceRef s b a) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

compare :: CoerceRef s b a -> CoerceRef s b a -> Ordering #

(<) :: CoerceRef s b a -> CoerceRef s b a -> Bool #

(<=) :: CoerceRef s b a -> CoerceRef s b a -> Bool #

(>) :: CoerceRef s b a -> CoerceRef s b a -> Bool #

(>=) :: CoerceRef s b a -> CoerceRef s b a -> Bool #

max :: CoerceRef s b a -> CoerceRef s b a -> CoerceRef s b a #

min :: CoerceRef s b a -> CoerceRef s b a -> CoerceRef s b a #

type HKD (CoerceRef s b :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Data.Mutable.Internal

type HKD (CoerceRef s b :: Type -> Type) (a :: Type) = Ref s a

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 CoerceRef s b a just as a normal data type, independent of the Ref 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 CoerceRef s b a just as a normal data type, independent of the Ref 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 CoerceRef s b a just as a normal data type, independent of the Ref 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 CoerceRef s b a just as a normal data type, independent of the Ref 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 CoerceRef s b a just as a normal data type, independent of the Ref 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 CoerceRef s b a just as a normal data type, independent of the Ref 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 CoerceRef s b a just as a normal data type, independent of the Ref 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> 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

Instances details
(Traversable f, Mutable s a) => DefaultMutable s (f a) (TraverseRef s f a) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: (PrimMonad m, PrimState m ~ s) => f a -> m (TraverseRef s f a) Source #

defaultFreezeRef :: (PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (f a) Source #

defaultCopyRef :: (PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> f a -> m () Source #

defaultMoveRef :: (PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> TraverseRef s f a -> m () Source #

defaultCloneRef :: (PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (TraverseRef s f a) Source #

defaultUnsafeThawRef :: (PrimMonad m, PrimState m ~ s) => f a -> m (TraverseRef s f a) Source #

defaultUnsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => TraverseRef s f a -> m (f a) Source #

IsoHKD (TraverseRef s f :: Type -> Type) (a :: Type) Source #

Use a TraverseRef s f a as if it were a f (Ref s a)

Instance details

Defined in Data.Mutable.Internal

Associated Types

type HKD (TraverseRef s f) a #

Methods

unHKD :: HKD (TraverseRef s f) a -> TraverseRef s f a #

toHKD :: TraverseRef s f a -> HKD (TraverseRef s f) a #

type HKD (TraverseRef s f :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Data.Mutable.Internal

type HKD (TraverseRef s f :: Type -> Type) (a :: Type) = f (Ref s a)

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 TraverseRef m f a just as a normal data type, independent of the Ref 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 TraverseRef m f a just as a normal data type, independent of the Ref 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 TraverseRef m f a just as a normal data type, independent of the Ref class. See documentation for TraverseRef for more information.

moveTraverse Source #

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 TraverseRef m f a just as a normal data type, independent of the Ref 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 TraverseRef m f a just as a normal data type, independent of the Ref 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 TraverseRef m f a just as a normal data type, independent of the Ref 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 TraverseRef m f a just as a normal data type, independent of the Ref 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

Instances details
DefaultMutable s a (ImmutableRef s a) Source # 
Instance details

Defined in Data.Mutable.Internal

IsoHKD (ImmutableRef s :: Type -> Type) (a :: Type) Source #

Use a ImmutableRef a as if it were an a

Instance details

Defined in Data.Mutable.Internal

Associated Types

type HKD (ImmutableRef s) a #

Methods

unHKD :: HKD (ImmutableRef s) a -> ImmutableRef s a #

toHKD :: ImmutableRef s a -> HKD (ImmutableRef s) a #

type HKD (ImmutableRef s :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Data.Mutable.Internal

type HKD (ImmutableRef s :: Type -> Type) (a :: Type) = a

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 ImmutableRef s b a just as a normal data type, independent of the Ref 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 ImmutableRef s b a just as a normal data type, independent of the Ref 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 ImmutableRef s b a just as a normal data type, independent of the Ref 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

Instances details
Eq (GRef_ s f a) => Eq (GMutableRef s f a) Source # 
Instance details

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

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 Ref m over every item in a type-level list

ghci> :kind! MapRef IO '[Int, V.Vector Double]
'[ MutVar RealWorld Int, MVector RealWorld Double ]

Equations

MapRef s '[] = '[] 
MapRef s (a ': as) = Ref s a ': MapRef s as 

Orphan instances

Mutable s () Source # 
Instance details

Associated Types

type Ref s () = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => () -> m (Ref s ()) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s () -> m () Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s () -> () -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s () -> Ref s () -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s () -> m (Ref s ()) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => () -> m (Ref s ()) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s () -> m () Source #

Mutable s Void Source # 
Instance details

Associated Types

type Ref s Void = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Void -> m (Ref s Void) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Void -> m Void Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Void -> Void -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Void -> Ref s Void -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Void -> m (Ref s Void) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Void -> m (Ref s Void) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Void -> m Void Source #

Mutable s ByteArray Source # 
Instance details

Associated Types

type Ref s ByteArray = (v :: Type) Source #

Mutable s CDouble Source # 
Instance details

Associated Types

type Ref s CDouble = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CDouble -> m (Ref s CDouble) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CDouble -> m CDouble Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CDouble -> CDouble -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CDouble -> Ref s CDouble -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CDouble -> m (Ref s CDouble) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CDouble -> m (Ref s CDouble) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CDouble -> m CDouble Source #

Mutable s CFloat Source # 
Instance details

Associated Types

type Ref s CFloat = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CFloat -> m (Ref s CFloat) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CFloat -> m CFloat Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CFloat -> CFloat -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CFloat -> Ref s CFloat -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CFloat -> m (Ref s CFloat) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CFloat -> m (Ref s CFloat) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CFloat -> m CFloat Source #

Mutable s CSUSeconds Source # 
Instance details

Associated Types

type Ref s CSUSeconds = (v :: Type) Source #

Mutable s CUSeconds Source # 
Instance details

Associated Types

type Ref s CUSeconds = (v :: Type) Source #

Mutable s CTime Source # 
Instance details

Associated Types

type Ref s CTime = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CTime -> m (Ref s CTime) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CTime -> m CTime Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CTime -> CTime -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CTime -> Ref s CTime -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CTime -> m (Ref s CTime) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CTime -> m (Ref s CTime) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CTime -> m CTime Source #

Mutable s CClock Source # 
Instance details

Associated Types

type Ref s CClock = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CClock -> m (Ref s CClock) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CClock -> m CClock Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CClock -> CClock -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CClock -> Ref s CClock -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CClock -> m (Ref s CClock) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CClock -> m (Ref s CClock) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CClock -> m CClock Source #

Mutable s CUIntMax Source # 
Instance details

Associated Types

type Ref s CUIntMax = (v :: Type) Source #

Mutable s CIntMax Source # 
Instance details

Associated Types

type Ref s CIntMax = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CIntMax -> m (Ref s CIntMax) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntMax -> m CIntMax Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntMax -> CIntMax -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntMax -> Ref s CIntMax -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntMax -> m (Ref s CIntMax) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CIntMax -> m (Ref s CIntMax) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntMax -> m CIntMax Source #

Mutable s CUIntPtr Source # 
Instance details

Associated Types

type Ref s CUIntPtr = (v :: Type) Source #

Mutable s CIntPtr Source # 
Instance details

Associated Types

type Ref s CIntPtr = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CIntPtr -> m (Ref s CIntPtr) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntPtr -> m CIntPtr Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntPtr -> CIntPtr -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntPtr -> Ref s CIntPtr -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntPtr -> m (Ref s CIntPtr) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CIntPtr -> m (Ref s CIntPtr) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CIntPtr -> m CIntPtr Source #

Mutable s CBool Source # 
Instance details

Associated Types

type Ref s CBool = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CBool -> m (Ref s CBool) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CBool -> m CBool Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CBool -> CBool -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CBool -> Ref s CBool -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CBool -> m (Ref s CBool) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CBool -> m (Ref s CBool) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CBool -> m CBool Source #

Mutable s CULLong Source # 
Instance details

Associated Types

type Ref s CULLong = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CULLong -> m (Ref s CULLong) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULLong -> m CULLong Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULLong -> CULLong -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULLong -> Ref s CULLong -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULLong -> m (Ref s CULLong) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CULLong -> m (Ref s CULLong) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULLong -> m CULLong Source #

Mutable s CLLong Source # 
Instance details

Associated Types

type Ref s CLLong = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CLLong -> m (Ref s CLLong) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLLong -> m CLLong Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLLong -> CLLong -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLLong -> Ref s CLLong -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLLong -> m (Ref s CLLong) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CLLong -> m (Ref s CLLong) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLLong -> m CLLong Source #

Mutable s CSigAtomic Source # 
Instance details

Associated Types

type Ref s CSigAtomic = (v :: Type) Source #

Mutable s CWchar Source # 
Instance details

Associated Types

type Ref s CWchar = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CWchar -> m (Ref s CWchar) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CWchar -> m CWchar Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CWchar -> CWchar -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CWchar -> Ref s CWchar -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CWchar -> m (Ref s CWchar) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CWchar -> m (Ref s CWchar) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CWchar -> m CWchar Source #

Mutable s CSize Source # 
Instance details

Associated Types

type Ref s CSize = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CSize -> m (Ref s CSize) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSize -> m CSize Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSize -> CSize -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSize -> Ref s CSize -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSize -> m (Ref s CSize) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CSize -> m (Ref s CSize) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSize -> m CSize Source #

Mutable s CPtrdiff Source # 
Instance details

Associated Types

type Ref s CPtrdiff = (v :: Type) Source #

Mutable s CULong Source # 
Instance details

Associated Types

type Ref s CULong = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CULong -> m (Ref s CULong) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULong -> m CULong Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULong -> CULong -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULong -> Ref s CULong -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULong -> m (Ref s CULong) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CULong -> m (Ref s CULong) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CULong -> m CULong Source #

Mutable s CLong Source # 
Instance details

Associated Types

type Ref s CLong = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CLong -> m (Ref s CLong) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLong -> m CLong Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLong -> CLong -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLong -> Ref s CLong -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLong -> m (Ref s CLong) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CLong -> m (Ref s CLong) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CLong -> m CLong Source #

Mutable s CUInt Source # 
Instance details

Associated Types

type Ref s CUInt = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CUInt -> m (Ref s CUInt) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUInt -> m CUInt Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUInt -> CUInt -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUInt -> Ref s CUInt -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUInt -> m (Ref s CUInt) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CUInt -> m (Ref s CUInt) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUInt -> m CUInt Source #

Mutable s CInt Source # 
Instance details

Associated Types

type Ref s CInt = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CInt -> m (Ref s CInt) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CInt -> m CInt Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CInt -> CInt -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CInt -> Ref s CInt -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CInt -> m (Ref s CInt) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CInt -> m (Ref s CInt) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CInt -> m CInt Source #

Mutable s CUShort Source # 
Instance details

Associated Types

type Ref s CUShort = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CUShort -> m (Ref s CUShort) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUShort -> m CUShort Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUShort -> CUShort -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUShort -> Ref s CUShort -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUShort -> m (Ref s CUShort) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CUShort -> m (Ref s CUShort) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUShort -> m CUShort Source #

Mutable s CShort Source # 
Instance details

Associated Types

type Ref s CShort = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CShort -> m (Ref s CShort) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CShort -> m CShort Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CShort -> CShort -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CShort -> Ref s CShort -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CShort -> m (Ref s CShort) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CShort -> m (Ref s CShort) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CShort -> m CShort Source #

Mutable s CUChar Source # 
Instance details

Associated Types

type Ref s CUChar = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CUChar -> m (Ref s CUChar) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUChar -> m CUChar Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUChar -> CUChar -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUChar -> Ref s CUChar -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUChar -> m (Ref s CUChar) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CUChar -> m (Ref s CUChar) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CUChar -> m CUChar Source #

Mutable s CSChar Source # 
Instance details

Associated Types

type Ref s CSChar = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CSChar -> m (Ref s CSChar) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSChar -> m CSChar Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSChar -> CSChar -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSChar -> Ref s CSChar -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSChar -> m (Ref s CSChar) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CSChar -> m (Ref s CSChar) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CSChar -> m CSChar Source #

Mutable s CChar Source # 
Instance details

Associated Types

type Ref s CChar = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => CChar -> m (Ref s CChar) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CChar -> m CChar Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s CChar -> CChar -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s CChar -> Ref s CChar -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s CChar -> m (Ref s CChar) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => CChar -> m (Ref s CChar) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s CChar -> m CChar Source #

Mutable s Word64 Source # 
Instance details

Associated Types

type Ref s Word64 = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Word64 -> m (Ref s Word64) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word64 -> m Word64 Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word64 -> Word64 -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word64 -> Ref s Word64 -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word64 -> m (Ref s Word64) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Word64 -> m (Ref s Word64) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word64 -> m Word64 Source #

Mutable s Word16 Source # 
Instance details

Associated Types

type Ref s Word16 = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Word16 -> m (Ref s Word16) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word16 -> m Word16 Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word16 -> Word16 -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word16 -> Ref s Word16 -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word16 -> m (Ref s Word16) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Word16 -> m (Ref s Word16) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word16 -> m Word16 Source #

Mutable s Word8 Source # 
Instance details

Associated Types

type Ref s Word8 = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Word8 -> m (Ref s Word8) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word8 -> m Word8 Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word8 -> Word8 -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word8 -> Ref s Word8 -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word8 -> m (Ref s Word8) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Word8 -> m (Ref s Word8) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word8 -> m Word8 Source #

Mutable s Word Source # 
Instance details

Associated Types

type Ref s Word = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Word -> m (Ref s Word) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word -> m Word Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word -> Word -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word -> Ref s Word -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word -> m (Ref s Word) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Word -> m (Ref s Word) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Word -> m Word Source #

Mutable s Char Source # 
Instance details

Associated Types

type Ref s Char = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Char -> m (Ref s Char) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Char -> m Char Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Char -> Char -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Char -> Ref s Char -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Char -> m (Ref s Char) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Char -> m (Ref s Char) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Char -> m Char Source #

Mutable s Bool Source # 
Instance details

Associated Types

type Ref s Bool = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Bool -> m (Ref s Bool) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Bool -> m Bool Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Bool -> Bool -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Bool -> Ref s Bool -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Bool -> m (Ref s Bool) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Bool -> m (Ref s Bool) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Bool -> m Bool Source #

Mutable s Double Source # 
Instance details

Associated Types

type Ref s Double = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Double -> m (Ref s Double) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Double -> m Double Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Double -> Double -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Double -> Ref s Double -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Double -> m (Ref s Double) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Double -> m (Ref s Double) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Double -> m Double Source #

Mutable s Float Source # 
Instance details

Associated Types

type Ref s Float = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Float -> m (Ref s Float) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Float -> m Float Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Float -> Float -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Float -> Ref s Float -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Float -> m (Ref s Float) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Float -> m (Ref s Float) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Float -> m Float Source #

Mutable s Natural Source # 
Instance details

Associated Types

type Ref s Natural = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Natural -> m (Ref s Natural) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Natural -> m Natural Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Natural -> Natural -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Natural -> Ref s Natural -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Natural -> m (Ref s Natural) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Natural -> m (Ref s Natural) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Natural -> m Natural Source #

Mutable s Integer Source # 
Instance details

Associated Types

type Ref s Integer = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Integer -> m (Ref s Integer) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Integer -> m Integer Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Integer -> Integer -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Integer -> Ref s Integer -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Integer -> m (Ref s Integer) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Integer -> m (Ref s Integer) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Integer -> m Integer Source #

Mutable s Int Source # 
Instance details

Associated Types

type Ref s Int = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Int -> m (Ref s Int) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Int -> m Int Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s Int -> Int -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s Int -> Ref s Int -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s Int -> m (Ref s Int) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Int -> m (Ref s Int) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s Int -> m Int Source #

Prim a => Mutable s (PrimArray a) Source # 
Instance details

Associated Types

type Ref s (PrimArray a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => PrimArray a -> m (Ref s (PrimArray a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (PrimArray a) -> m (PrimArray a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (PrimArray a) -> PrimArray a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (PrimArray a) -> Ref s (PrimArray a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (PrimArray a) -> m (Ref s (PrimArray a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => PrimArray a -> m (Ref s (PrimArray a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (PrimArray a) -> m (PrimArray a) Source #

Mutable s (SmallArray a) Source # 
Instance details

Associated Types

type Ref s (SmallArray a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => SmallArray a -> m (Ref s (SmallArray a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (SmallArray a) -> m (SmallArray a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (SmallArray a) -> SmallArray a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (SmallArray a) -> Ref s (SmallArray a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (SmallArray a) -> m (Ref s (SmallArray a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => SmallArray a -> m (Ref s (SmallArray a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (SmallArray a) -> m (SmallArray a) Source #

Mutable s (Array a) Source # 
Instance details

Associated Types

type Ref s (Array a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Array a -> m (Ref s (Array a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Array a) -> m (Array a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Array a) -> Array a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Array a) -> Ref s (Array a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Array a) -> m (Ref s (Array a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Array a -> m (Ref s (Array a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Array a) -> m (Array a) Source #

Prim a => Mutable s (Vector a) Source #

Mutable reference is MVector.

Instance details

Associated Types

type Ref s (Vector a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Vector a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Ref s (Vector a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Ref s (Vector a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

Unbox a => Mutable s (Vector a) Source #

Mutable reference is MVector.

Instance details

Associated Types

type Ref s (Vector a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Vector a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Ref s (Vector a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Ref s (Vector a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

Storable a => Mutable s (Vector a) Source #

Mutable reference is MVector.

Instance details

Associated Types

type Ref s (Vector a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Vector a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Ref s (Vector a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Ref s (Vector a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

Mutable s (Vector a) Source #

Mutable reference is MVector.

Instance details

Associated Types

type Ref s (Vector a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Vector a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> Ref s (Vector a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Ref s (Vector a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Vector a -> m (Ref s (Vector a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Vector a) -> m (Vector a) Source #

Mutable s a => Mutable s (Identity a) Source #

Meant for usage with higher-kinded data pattern (See HKD)

Instance details

Associated Types

type Ref s (Identity a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Identity a -> m (Ref s (Identity a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> m (Identity a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> Identity a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> Ref s (Identity a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> m (Ref s (Identity a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Identity a -> m (Ref s (Identity a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> m (Identity a) Source #

Mutable s a => Mutable s [a] Source #

Mutable linked list with mutable references in each cell. See MutBranch documentation for an example of using this as a mutable linked list.l

Instance details

Associated Types

type Ref s [a] = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => [a] -> m (Ref s [a]) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s [a] -> m [a] Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s [a] -> [a] -> m () Source #

moveRef :: (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 #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => [a] -> m (Ref s [a]) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s [a] -> m [a] Source #

Mutable s a => Mutable s (Maybe a) Source # 
Instance details

Associated Types

type Ref s (Maybe a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Maybe a -> m (Ref s (Maybe a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Maybe a) -> m (Maybe a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Maybe a) -> Maybe a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Maybe a) -> Ref s (Maybe a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Maybe a) -> m (Ref s (Maybe a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Maybe a -> m (Ref s (Maybe a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Maybe a) -> m (Maybe a) Source #

Mutable s a => Mutable s (Dual a) Source # 
Instance details

Associated Types

type Ref s (Dual a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Dual a -> m (Ref s (Dual a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Dual a) -> m (Dual a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Dual a) -> Dual a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Dual a) -> Ref s (Dual a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Dual a) -> m (Ref s (Dual a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Dual a -> m (Ref s (Dual a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Dual a) -> m (Dual a) Source #

Mutable s a => Mutable s (Down a) Source # 
Instance details

Associated Types

type Ref s (Down a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Down a -> m (Ref s (Down a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Down a) -> m (Down a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Down a) -> Down a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Down a) -> Ref s (Down a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Down a) -> m (Ref s (Down a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Down a -> m (Ref s (Down a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Down a) -> m (Down a) Source #

Mutable s a => Mutable s (Sum a) Source # 
Instance details

Associated Types

type Ref s (Sum a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Sum a -> m (Ref s (Sum a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum a) -> m (Sum a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum a) -> Sum a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum a) -> Ref s (Sum a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum a) -> m (Ref s (Sum a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Sum a -> m (Ref s (Sum a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum a) -> m (Sum a) Source #

Mutable s a => Mutable s (Product a) Source # 
Instance details

Associated Types

type Ref s (Product a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Product a -> m (Ref s (Product a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product a) -> m (Product a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product a) -> Product a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product a) -> Ref s (Product a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product a) -> m (Ref s (Product a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Product a -> m (Ref s (Product a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product a) -> m (Product a) Source #

Mutable s a => Mutable s (Identity a) Source # 
Instance details

Associated Types

type Ref s (Identity a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Identity a -> m (Ref s (Identity a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> m (Identity a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> Identity a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> Ref s (Identity a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> m (Ref s (Identity a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Identity a -> m (Ref s (Identity a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Identity a) -> m (Identity a) Source #

Mutable s (Complex a) Source # 
Instance details

Associated Types

type Ref s (Complex a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Complex a -> m (Ref s (Complex a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Complex a) -> m (Complex a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Complex a) -> Complex a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Complex a) -> Ref s (Complex a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Complex a) -> m (Ref s (Complex a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Complex a -> m (Ref s (Complex a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Complex a) -> m (Complex a) Source #

Mutable s (Ratio a) Source # 
Instance details

Associated Types

type Ref s (Ratio a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Ratio a -> m (Ref s (Ratio a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Ratio a) -> m (Ratio a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Ratio a) -> Ratio a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Ratio a) -> Ref s (Ratio a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Ratio a) -> m (Ref s (Ratio a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Ratio a -> m (Ref s (Ratio a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Ratio a) -> m (Ratio a) Source #

(Mutable s a, Mutable s (HList as), Ref s (HList as) ~ HListRef s as) => Mutable s (HList (a ': as)) Source # 
Instance details

Associated Types

type Ref s (HList (a ': as)) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => HList (a ': as) -> m (Ref s (HList (a ': as))) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList (a ': as)) -> m (HList (a ': as)) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList (a ': as)) -> HList (a ': as) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList (a ': as)) -> Ref s (HList (a ': as)) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList (a ': as)) -> m (Ref s (HList (a ': as))) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => HList (a ': as) -> m (Ref s (HList (a ': as))) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList (a ': as)) -> m (HList (a ': as)) Source #

Mutable s (HList ('[] :: [Type])) Source # 
Instance details

Associated Types

type Ref s (HList '[]) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => HList '[] -> m (Ref s (HList '[])) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList '[]) -> m (HList '[]) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList '[]) -> HList '[] -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList '[]) -> Ref s (HList '[]) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList '[]) -> m (Ref s (HList '[])) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => HList '[] -> m (Ref s (HList '[])) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (HList '[]) -> m (HList '[]) Source #

(Mutable s a, Mutable s b) => Mutable s (a, b) Source #

A Ref of a tuple is a tuple of Refs, for easy accessing.

Ref s (Int, Vector Double) = (MutVar s Int, MVector s Double)
Instance details

Associated Types

type Ref s (a, b) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b) -> m (Ref s (a, b)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b) -> m (a, b) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b) -> (a, b) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b) -> Ref s (a, b) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b) -> m (Ref s (a, b)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b) -> m (Ref s (a, b)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b) -> m (a, b) Source #

(Mutable s a, Mutable s b) => Mutable s (Either a b) Source # 
Instance details

Associated Types

type Ref s (Either a b) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Either a b -> m (Ref s (Either a b)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Either a b) -> m (Either a b) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Either a b) -> Either a b -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Either a b) -> Ref s (Either a b) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Either a b) -> m (Ref s (Either a b)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Either a b -> m (Ref s (Either a b)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Either a b) -> m (Either a b) Source #

Mutable s a => Mutable s (Const a b) Source # 
Instance details

Associated Types

type Ref s (Const a b) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Const a b -> m (Ref s (Const a b)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> m (Const a b) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> Const a b -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> Ref s (Const a b) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> m (Ref s (Const a b)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Const a b -> m (Ref s (Const a b)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> m (Const a b) Source #

Mutable s a => Mutable s (Const a b) Source # 
Instance details

Associated Types

type Ref s (Const a b) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Const a b -> m (Ref s (Const a b)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> m (Const a b) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> Const a b -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> Ref s (Const a b) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> m (Ref s (Const a b)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Const a b -> m (Ref s (Const a b)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Const a b) -> m (Const a b) Source #

(RecApplicative as, NatToInt (RLength as), RPureConstrained (IndexableField as) as, Mutable s (Rec f as), Ref s (Rec f as) ~ Rec (RecRef s f) as) => Mutable s (ARec f as) Source # 
Instance details

Associated Types

type Ref s (ARec f as) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => ARec f as -> m (Ref s (ARec f as)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (ARec f as) -> m (ARec f as) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (ARec f as) -> ARec f as -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (ARec f as) -> Ref s (ARec f as) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (ARec f as) -> m (Ref s (ARec f as)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => ARec f as -> m (Ref s (ARec f as)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (ARec f as) -> m (ARec f as) Source #

(Mutable s (f a2), Mutable s (Rec f as), Ref s (Rec f as) ~ Rec (RecRef s f) as) => Mutable s (Rec f (a2 ': as)) Source # 
Instance details

Associated Types

type Ref s (Rec f (a2 ': as)) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Rec f (a2 ': as) -> m (Ref s (Rec f (a2 ': as))) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f (a2 ': as)) -> m (Rec f (a2 ': as)) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f (a2 ': as)) -> Rec f (a2 ': as) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f (a2 ': as)) -> Ref s (Rec f (a2 ': as)) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f (a2 ': as)) -> m (Ref s (Rec f (a2 ': as))) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Rec f (a2 ': as) -> m (Ref s (Rec f (a2 ': as))) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f (a2 ': as)) -> m (Rec f (a2 ': as)) Source #

Mutable s (Rec f ('[] :: [u])) Source # 
Instance details

Associated Types

type Ref s (Rec f '[]) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Rec f '[] -> m (Ref s (Rec f '[])) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f '[]) -> m (Rec f '[]) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f '[]) -> Rec f '[] -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f '[]) -> Ref s (Rec f '[]) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f '[]) -> m (Ref s (Rec f '[])) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Rec f '[] -> m (Ref s (Rec f '[])) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Rec f '[]) -> m (Rec f '[]) Source #

(Mutable s a, Mutable s b, Mutable s c) => Mutable s (a, b, c) Source # 
Instance details

Associated Types

type Ref s (a, b, c) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c) -> m (Ref s (a, b, c)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c) -> m (a, b, c) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c) -> (a, b, c) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c) -> Ref s (a, b, c) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c) -> m (Ref s (a, b, c)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c) -> m (Ref s (a, b, c)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c) -> m (a, b, c) Source #

(Mutable s (f a), Mutable s (g a)) => Mutable s (Sum f g a) Source # 
Instance details

Associated Types

type Ref s (Sum f g a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Sum f g a -> m (Ref s (Sum f g a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum f g a) -> m (Sum f g a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum f g a) -> Sum f g a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum f g a) -> Ref s (Sum f g a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum f g a) -> m (Ref s (Sum f g a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Sum f g a -> m (Ref s (Sum f g a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Sum f g a) -> m (Sum f g a) Source #

(Mutable s (f a), Mutable s (g a)) => Mutable s (Product f g a) Source # 
Instance details

Associated Types

type Ref s (Product f g a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Product f g a -> m (Ref s (Product f g a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product f g a) -> m (Product f g a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product f g a) -> Product f g a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product f g a) -> Ref s (Product f g a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product f g a) -> m (Ref s (Product f g a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Product f g a -> m (Ref s (Product f g a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Product f g a) -> m (Product f g a) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d) => Mutable s (a, b, c, d) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d) -> m (Ref s (a, b, c, d)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d) -> m (a, b, c, d) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d) -> (a, b, c, d) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d) -> Ref s (a, b, c, d) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d) -> m (Ref s (a, b, c, d)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d) -> m (Ref s (a, b, c, d)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d) -> m (a, b, c, d) Source #

Mutable s (f (g a)) => Mutable s (Compose f g a) Source # 
Instance details

Associated Types

type Ref s (Compose f g a) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => Compose f g a -> m (Ref s (Compose f g a)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Compose f g a) -> m (Compose f g a) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Compose f g a) -> Compose f g a -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Compose f g a) -> Ref s (Compose f g a) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Compose f g a) -> m (Ref s (Compose f g a)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => Compose f g a -> m (Ref s (Compose f g a)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (Compose f g a) -> m (Compose f g a) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e) => Mutable s (a, b, c, d, e) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e) -> m (Ref s (a, b, c, d, e)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e) -> m (a, b, c, d, e) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e) -> (a, b, c, d, e) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e) -> Ref s (a, b, c, d, e) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e) -> m (Ref s (a, b, c, d, e)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e) -> m (Ref s (a, b, c, d, e)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e) -> m (a, b, c, d, e) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e, Mutable s f) => Mutable s (a, b, c, d, e, f) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e, f) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f) -> m (Ref s (a, b, c, d, e, f)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f) -> m (a, b, c, d, e, f) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f) -> Ref s (a, b, c, d, e, f) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f) -> m (Ref s (a, b, c, d, e, f)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f) -> m (Ref s (a, b, c, d, e, f)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f) -> m (a, b, c, d, e, f) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e, Mutable s f, Mutable s g) => Mutable s (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e, f, g) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g) -> m (Ref s (a, b, c, d, e, f, g)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g) -> Ref s (a, b, c, d, e, f, g) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g) -> m (Ref s (a, b, c, d, e, f, g)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g) -> m (Ref s (a, b, c, d, e, f, g)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e, Mutable s f, Mutable s g, Mutable s h) => Mutable s (a, b, c, d, e, f, g, h) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e, f, g, h) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h) -> m (Ref s (a, b, c, d, e, f, g, h)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h) -> m (a, b, c, d, e, f, g, h) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h) -> Ref s (a, b, c, d, e, f, g, h) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h) -> m (Ref s (a, b, c, d, e, f, g, h)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h) -> m (Ref s (a, b, c, d, e, f, g, h)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h) -> m (a, b, c, d, e, f, g, h) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e, Mutable s f, Mutable s g, Mutable s h, Mutable s i) => Mutable s (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e, f, g, h, i) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i) -> m (Ref s (a, b, c, d, e, f, g, h, i)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i) -> m (a, b, c, d, e, f, g, h, i) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i) -> Ref s (a, b, c, d, e, f, g, h, i) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i) -> m (Ref s (a, b, c, d, e, f, g, h, i)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i) -> m (Ref s (a, b, c, d, e, f, g, h, i)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i) -> m (a, b, c, d, e, f, g, h, i) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e, Mutable s f, Mutable s g, Mutable s h, Mutable s i, Mutable s j) => Mutable s (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e, f, g, h, i, j) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i, j) -> m (Ref s (a, b, c, d, e, f, g, h, i, j)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j) -> m (a, b, c, d, e, f, g, h, i, j) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j) -> Ref s (a, b, c, d, e, f, g, h, i, j) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j) -> m (Ref s (a, b, c, d, e, f, g, h, i, j)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i, j) -> m (Ref s (a, b, c, d, e, f, g, h, i, j)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j) -> m (a, b, c, d, e, f, g, h, i, j) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e, Mutable s f, Mutable s g, Mutable s h, Mutable s i, Mutable s j, Mutable s k) => Mutable s (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e, f, g, h, i, j, k) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i, j, k) -> m (Ref s (a, b, c, d, e, f, g, h, i, j, k)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k) -> m (a, b, c, d, e, f, g, h, i, j, k) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k) -> Ref s (a, b, c, d, e, f, g, h, i, j, k) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k) -> m (Ref s (a, b, c, d, e, f, g, h, i, j, k)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i, j, k) -> m (Ref s (a, b, c, d, e, f, g, h, i, j, k)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k) -> m (a, b, c, d, e, f, g, h, i, j, k) Source #

(Mutable s a, Mutable s b, Mutable s c, Mutable s d, Mutable s e, Mutable s f, Mutable s g, Mutable s h, Mutable s i, Mutable s j, Mutable s k, Mutable s l) => Mutable s (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Associated Types

type Ref s (a, b, c, d, e, f, g, h, i, j, k, l) = (v :: Type) Source #

Methods

thawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i, j, k, l) -> m (Ref s (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

freezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k, l) -> m (a, b, c, d, e, f, g, h, i, j, k, l) Source #

copyRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> m () Source #

moveRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k, l) -> Ref s (a, b, c, d, e, f, g, h, i, j, k, l) -> m () Source #

cloneRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k, l) -> m (Ref s (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

unsafeThawRef :: (PrimMonad m, PrimState m ~ s) => (a, b, c, d, e, f, g, h, i, j, k, l) -> m (Ref s (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (a, b, c, d, e, f, g, h, i, j, k, l) -> m (a, b, c, d, e, f, g, h, i, j, k, l) Source #