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

Description

Main entrypoint of the package. Abstract over different types for piecewise-mutable references of values.

See https://mutable.jle.im/ for a comprehensive introduction.

Synopsis

Documentation

class Mutable s a where Source #

An instance of Mutable s a means that a can be stored a mutable reference in a PrimMonad m (where s is the mutable state token PrimState of that monad).

The associated type Ref s a links any a to the type of its canonical mutable version.

The benefit of this typeclass, instead of just using IORef or MutVar or specific mutable versions like Vector and MVector, is two-fold:

  • Piecewise-mutable values, so you can write to only one part and not others. This also allows for cheaper "writes", even if you replace the whole value: you don't need to ever synthesize an entire new value, you can keep each component in a separate variable until you freezeRef it out. This can be especially useful for composite data types containing large structures like Vector.
  • Generic abstractions (similar to Show), so you can automatically derive instances while preserving piecewise-ness. For example, the instance

    instance (Mutable s a, Mutable s b) => Mutable s (a, b)
    

    If a and b are piecwise-mutable, then the instance here will appropriately utilize that fact.

To modify the specific parts of mutable values, it can be useful to use the functions in Data.Mutable.Parts.

There are facilities to automatically piecewise mutable versions for user-defined instances of Generic.

For example, if we have a type like:

data TwoVectors = TV
    { tvInt    :: Vector Int
    , tvDouble :: Vector Double
    }
  deriving Generic

instance Mutable s TwoVectors where
    type Ref s TwoVectors = GRef s TwoVectors

Then now we get:

thawRef   :: TwoVectors -> m (GRef s TwoVectors)
freezeRef :: GRef s TwoVectors -> m TwoVectors

And GRef s TwoVectors is now a piecewise-mutable reference storing each part in a way that can be modified separately (for example, with tools from Data.Mutable.Parts). It does this by internally allocating two MVectors. If the two vectors are large, this can be much more efficient to modify (if you are modifying several times) than by just doing alterations on TwoVectors. It is also much better for large vectors if you plan on modifying only a single item in the vector.

If you are using the "higher-kinded" data pattern, a la https://reasonablypolymorphic.com/blog/higher-kinded-data/, then we can also do:

data TwoVectors f = TV
     { tvInt    :: HKD f (Vector Int)
     , tvDouble :: HKD f (Vector Double)
     }
  deriving Generic

instance Mutable (TwoVectors Identity) where
    type Ref (TwoVectors Identity) = TwoVectors (RefFor s)

And now your mutable ref is literally going to be a product of the components

ghci> tvr@(TV is ds) <- thawRef (TV xs ys)
ghci> :t tvr
TV (RefFor RealWorld)
ghci> :t is
MVector RealWorld Int
ghci> :t ds
MV.MVector RealWorld Double

So thawRef will actually just get you the same record type but with the mutable versions of each field. If you modify the mutable fields, and then later freezeRef the whole thing, the resulting frozen value will incorporate all of the changes to the individual fields.

In addition, there are a few more "automatically derived" instances you can get by picking Ref:

-- Make a mutable version for any newtype wrapper, using the Mutable
-- of the underlying type
newtype MyType = MT (Vector Double)

type Ref s MyType = CoerceRef s MyType (Vector Double)

-- Make a mutable version of any container, where the items are all
-- mutable references.
data MyContainer a = MC a a a a
  deriving (Functor, Foldable, Traversable)

type Ref s (MyContainer a) = TraverseRef s MyContainer a

See https://mutable.jle.im/02-mutable-and-ref.html for more information on this typeclass and how to define instances automatically, and also

Minimal complete definition

Nothing

Associated Types

type Ref s a = (v :: Type) | v -> a s Source #

Links the type a to the type of its canonical "mutable version".

For example, for Vector, the mutable version is MVector, so we have

type Ref s (Vector a) = MVector s a

This means that using thawRef on a Vector will give you an MVector, using freezeRef on a Vector will give you a Vector, etc.

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

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

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

This associated type must be unique for a, so no two types a can have the same Ref s a. This makes type inference a lot more useful: if you use freezeRef on an MVector, for instance, the return type will be inferred to be Vector.

The default instance is just a plain old MutVar containing the type. This is a valid instance, but it treats the entire type "wholesale" --- it is basically using it as a non-mutable type. You won't get any of the performance benefits of piecewise mutation from it, but it is useful as a base case for non-composite types like Int.

There are some built-in alternative options for user-defined ADTs with Generic instances:

-- Works for all Generic instances, preserves piecewise mutation
-- for products
type Ref s a = GRef s a

If you just set up a blank instance, the implementations of thawRef, freezeRef, and copyRef will be inferred using DefaultMutable.

data MyType

-- The default setup is OK
instance Mutable s MyType

-- This is equivalent to the above
instance Mutable s MyType
    type Ref s MyType = MutVar s MyType

-- any Generic instance
data MyType = MyType { mtInt :: Int, mtDouble :: Double }
  deriving Generic

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType

See https://mutable.jle.im/02-mutable-and-ref.html for more information on this type family and how to define instances automatically.

Note that this type synonym ins injective --- this means that if you write a function polymorphic over Ref s a, you can always infer s and a (the value stored in the Ref).

In practice, if you want to write your own instance from scratch, the consequence is that you must have the s type variable somewhere in your type (see UnitRef and VoidRef for examples).

type Ref s a = MutVar s a Source #

Methods

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

Thaw a pure/persistent value into its mutable version, which can be manipulated using modifyRef or other methods specific for that type (like read).

Returns the Ref instance, so, for example, for Vector:

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

For non-composite (like Int), this is often called the "new var" function, like newIORef / newSTRef / newMutVar etc.

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

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

Freeze a mutable value into its pure/persistent version.

Takes a Ref instance, but type inference will be able to infer the pure value's type because Ref is injective.

For example, for Vector:

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

For non-composite (like Int), this is often called the "read var" function, like readIORef / readSTRef / readMutVar etc.

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

copyRef Source #

Arguments

:: (PrimMonad m, PrimState m ~ s) 
=> Ref s a

destination to overwrite

-> a

value

-> m () 

Overwrite a mutable value by provivding a pure/persistent value. copyRef

Returns the Ref and the value, so, for example, for Vector:

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

Note that if a is a composite type (with an appropriate composite reference), this will be done "piecewise": it'll write to each mutable component separately.

For non-composite (like Int), this is often called the "write var" function, like writeIORef / writeSTRef / writeMutVar etc.

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

moveRef Source #

Arguments

:: (PrimMonad m, PrimState m ~ s) 
=> Ref s a

destination

-> Ref s a

source

-> m () 

Deep Copy-move a mutable reference on top of another, overwriting the second one.

For non-composite types, this is the same as a thawRef and a copyRef. For composite types this can be more effficient because the copying is done piecewise, so the intermediate pure value is never created.

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

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

Create a deep copy of a mutable reference, allocated to a separate independent reference.

For non-composite types, this is the same as a thawRef and a freezeRef. For composite types this can be more effficient because the cloning is done piecewise, so the intermediate pure value is never created.

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

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

A non-copying version of thawRef that can be more efficient for types where the mutable representation is the same as the immutable one (like Vector).

This is safe as long as you never again use the original pure value, since it can potentially directly mutate it.

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

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

A non-copying version of freezeRef that can be more efficient for types where the mutable representation is the same as the immutable one (like Vector).

This is safe as long as you never again modify the mutable reference, since it can potentially directly mutate the frozen value magically.

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

Instances

Instances details
Mutable s () Source # 
Instance details

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

Associated Types

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

Mutable s CDouble Source # 
Instance details

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

Associated Types

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

Mutable s CUSeconds Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Mutable s CTime Source # 
Instance details

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

Associated Types

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

Mutable s CIntMax Source # 
Instance details

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

Associated Types

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

Mutable s CIntPtr Source # 
Instance details

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

Associated Types

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

Mutable s CWchar Source # 
Instance details

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

Associated Types

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

Mutable s CULong Source # 
Instance details

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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 (VarMut a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

Mutable s (V1 a) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

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

Methods

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

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

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

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

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

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

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

Mutable s (U1 a) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

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

Methods

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

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

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

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

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

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

unsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => Ref s (U1 a) -> m (U1 a) 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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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 (Immutable s a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

(Mutable s a, Coercible s a) => Mutable s (CoerceMut s a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

(Traversable f, Mutable s a) => Mutable s (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

(GMutable s f, GMutable s g) => Mutable s ((f :+: g) a) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

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

Methods

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

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

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

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

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

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

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

(GMutable s f, GMutable s g) => Mutable s ((f :*: g) a) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

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

Methods

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

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

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

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

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

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

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

Mutable s c => Mutable s (K1 i c a) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

type Ref s (K1 i c a) = (v :: Type) Source #

Methods

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

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

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

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

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

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

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

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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

Defined in Data.Mutable.Instances

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 #

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

Apply a pure function on an immutable value onto a value stored in a mutable reference.

modifyRef' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => Ref s a -> (a -> a) -> m () Source #

modifyRef, but forces the result before storing it back in the reference.

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

Apply a pure function on an immutable value onto a value stored in a mutable reference, returning a result value from that function.

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

updateRef, but forces the updated value before storing it back in the reference.

newtype RefFor s a Source #

A handy newtype wrapper that allows you to partially apply Ref. RefFor m a is the same as Ref s a, but can be partially applied.

If used with HKD, you can treat this syntactically identically as a Ref s a.

Constructors

RefFor 

Fields

Instances

Instances details
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z (K1 i (RefFor s c) :: k -> Type) (K1 i (MutPart s (z Identity) c) :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> K1 i (RefFor s c) a) -> K1 i (MutPart s (z Identity) c) a

(Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s))) => DefaultMutable s (z Identity) (z (RefFor s)) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: (PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s)) Source #

defaultFreezeRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity) Source #

defaultCopyRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z Identity -> m () Source #

defaultMoveRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z (RefFor s) -> m () Source #

defaultCloneRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z (RefFor s)) Source #

defaultUnsafeThawRef :: (PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s)) Source #

defaultUnsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity) Source #

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

Use a RefFor m a as if it were a Ref s a.

Instance details

Defined in Data.Mutable.Internal

Associated Types

type HKD (RefFor s) a #

Methods

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

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

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

Defined in Data.Mutable.Internal

Methods

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

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

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

Defined in Data.Mutable.Internal

Methods

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

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

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

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

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

max :: RefFor s a -> RefFor s a -> RefFor s a #

min :: RefFor s a -> RefFor s a -> RefFor s a #

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

Defined in Data.Mutable.Internal

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

Instances

class DefaultMutable s a r | r -> a s Source #

The default implementations of thawRef, freezeRef, and copyRef dispatched for different choices of Ref.

Basically, by specifying Ref, you get the rest of the instance for free.

We have the default case:

-- default, if you don't specify Ref
instance Mutable s MyType

-- the above is the same as:
instance Mutable s MyType
    type Ref s MyType = MutVar s) MyType

The case for any instance of Generic:

instance Mutable s MyType
    type Ref s MyType = GRef s MyType

The case for the "higher-kinded data" pattern a la https://reasonablypolymorphic.com/blog/higher-kinded-data/:

instance Mutable s (MyTypeF Identity)
    type Ref s (MyTypeF Identity) = MyTypeF (RefFor s)

The case for any newtype wrapper:

newtype MyType = MT (Vector Double)

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

And the case for any 'Traversable instance, where the items will all be mutable references:

data MyContainer a = MC a a a a
  deriving (Functor, Foldable, Traversable)

instance Mutable s a => Mutable s (MyContainer a) where
    type Ref s (MyContainer a) = TraverseRef s MyContainer a

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 #

DefaultMutable s a (MutVar s a) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

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

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

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

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

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

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

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

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

Defined in Data.Mutable.Internal

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

(Generic (z Identity), Generic (z (RefFor s)), GMutable s (Rep (z Identity)), GRef_ s (Rep (z Identity)) ~ Rep (z (RefFor s))) => DefaultMutable s (z Identity) (z (RefFor s)) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: (PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s)) Source #

defaultFreezeRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity) Source #

defaultCopyRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z Identity -> m () Source #

defaultMoveRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> z (RefFor s) -> m () Source #

defaultCloneRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z (RefFor s)) Source #

defaultUnsafeThawRef :: (PrimMonad m, PrimState m ~ s) => z Identity -> m (z (RefFor s)) Source #

defaultUnsafeFreezeRef :: (PrimMonad m, PrimState m ~ s) => z (RefFor s) -> m (z Identity) Source #

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

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

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 #

data MutVar s a #

A MutVar behaves like a single-element mutable array associated with a primitive state token.

Instances

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

Defined in Data.Mutable.Internal

Methods

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

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

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

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

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

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

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

Eq (MutVar s a) 
Instance details

Defined in Data.Primitive.MutVar

Methods

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

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

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

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)

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

Providing/overriding instances

newtype VarMut a Source #

Newtype wrapper that can provide any type with a Mutable instance, giving it a "non-piecewise" instance. Can be useful for avoiding orphan instances yet still utilizing auto-deriving features, or for overwriting the Mutable instance of other instances.

For example, let's say you want to auto-derive an instance for your data type:

data MyType = MT Int Double OtherType
  deriving Generic

This is possible if all of MyTypes fields have Mutable instances. However, let's say OtherType comes from an external library that you don't have control over, and so you cannot give it a Mutable instance without incurring an orphan instance.

One solution is to wrap it in VarMut:

data MyType = MT Int Double (VarMut OtherType)
  deriving Generic

This can then be auto-derived:

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType

It can also be used to override a Mutable instance. For example, even if the Mutable instance of SomeType is piecewise-mutable, the Mutable instance of VarMut SomeType will be not be piecewise.

For example, the Mutable instance for String is a mutable linked list, but it might be more efficient to treat it as an atomic value to update all at once. You can use VarMut String to get that Mutable instance.

Constructors

VarMut 

Fields

Instances

Instances details
Mutable s (VarMut a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

IsoHKD VarMut (a :: Type) Source #

Use a VarMut a as if it were an a.

Instance details

Defined in Data.Mutable.Class

Associated Types

type HKD VarMut a #

Methods

unHKD :: HKD VarMut a -> VarMut a #

toHKD :: VarMut a -> HKD VarMut a #

type Ref s (VarMut a) Source # 
Instance details

Defined in Data.Mutable.Class

type Ref s (VarMut a) = MutVar s (VarMut a)
type HKD VarMut (a :: Type) Source # 
Instance details

Defined in Data.Mutable.Class

type HKD VarMut (a :: Type) = a

newtype CoerceMut s a Source #

Similar to VarMut, this allows you to overwrite the normal Mutable instance of a type to utilize a coercible type's Mutable instance instead of its normal instance. It's also useful to provide an instance for an externally defined type without incurring orphan instances.

For example, if an external library provides

newtype DoubleVec = DV (Vector Double)

and you want to use it following Vectors Mutable instance (via MVector), but you don't want to write an orphan instance like

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

then you can instead use CoerceMut DoubleVec (Vector Double) as the data type. This wrapped type does use the inderlying Mutable insatnce for Vector.

Constructors

CoerceMut 

Fields

Instances

Instances details
IsoHKD (CoerceMut s :: k -> Type) (a :: k) Source #

Use a CoerceMut s a as if it were an s

Instance details

Defined in Data.Mutable.Class

Associated Types

type HKD (CoerceMut s) a #

Methods

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

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

(Mutable s a, Coercible s a) => Mutable s (CoerceMut s a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

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

Defined in Data.Mutable.Class

type HKD (CoerceMut s :: k -> Type) (a :: k) = s
type Ref s (CoerceMut s a) Source # 
Instance details

Defined in Data.Mutable.Class

type Ref s (CoerceMut s a) = CoerceRef s (CoerceMut s a) a

newtype TraverseMut f a Source #

Similar to VarMut, this allows you to overwrite the normal Mutable instance for a type to utilize its Traversable instance instead of its normal instance. It's also useful to provide an instance for an externally defined type without incurring orphan instances.

For example, the instance of Mutable (TraverseMut [] a) is a normal list of mutable references, instead of a full-on mutable linked list.

Constructors

TraverseMut 

Fields

Instances

Instances details
IsoHKD (TraverseMut f :: k -> Type) (a :: k) Source #

Use a TraverseMut f a as if it were an f a

Instance details

Defined in Data.Mutable.Class

Associated Types

type HKD (TraverseMut f) a #

Methods

unHKD :: HKD (TraverseMut f) a -> TraverseMut f a #

toHKD :: TraverseMut f a -> HKD (TraverseMut f) a #

(Traversable f, Mutable s a) => Mutable s (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

Functor f => Functor (TraverseMut f) Source # 
Instance details

Defined in Data.Mutable.Class

Methods

fmap :: (a -> b) -> TraverseMut f a -> TraverseMut f b #

(<$) :: a -> TraverseMut f b -> TraverseMut f a #

Foldable f => Foldable (TraverseMut f) Source # 
Instance details

Defined in Data.Mutable.Class

Methods

fold :: Monoid m => TraverseMut f m -> m #

foldMap :: Monoid m => (a -> m) -> TraverseMut f a -> m #

foldMap' :: Monoid m => (a -> m) -> TraverseMut f a -> m #

foldr :: (a -> b -> b) -> b -> TraverseMut f a -> b #

foldr' :: (a -> b -> b) -> b -> TraverseMut f a -> b #

foldl :: (b -> a -> b) -> b -> TraverseMut f a -> b #

foldl' :: (b -> a -> b) -> b -> TraverseMut f a -> b #

foldr1 :: (a -> a -> a) -> TraverseMut f a -> a #

foldl1 :: (a -> a -> a) -> TraverseMut f a -> a #

toList :: TraverseMut f a -> [a] #

null :: TraverseMut f a -> Bool #

length :: TraverseMut f a -> Int #

elem :: Eq a => a -> TraverseMut f a -> Bool #

maximum :: Ord a => TraverseMut f a -> a #

minimum :: Ord a => TraverseMut f a -> a #

sum :: Num a => TraverseMut f a -> a #

product :: Num a => TraverseMut f a -> a #

Traversable f => Traversable (TraverseMut f) Source # 
Instance details

Defined in Data.Mutable.Class

Methods

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

sequenceA :: Applicative f0 => TraverseMut f (f0 a) -> f0 (TraverseMut f a) #

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

sequence :: Monad m => TraverseMut f (m a) -> m (TraverseMut f a) #

Eq (f a) => Eq (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

Methods

(==) :: TraverseMut f a -> TraverseMut f a -> Bool #

(/=) :: TraverseMut f a -> TraverseMut f a -> Bool #

Ord (f a) => Ord (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

Methods

compare :: TraverseMut f a -> TraverseMut f a -> Ordering #

(<) :: TraverseMut f a -> TraverseMut f a -> Bool #

(<=) :: TraverseMut f a -> TraverseMut f a -> Bool #

(>) :: TraverseMut f a -> TraverseMut f a -> Bool #

(>=) :: TraverseMut f a -> TraverseMut f a -> Bool #

max :: TraverseMut f a -> TraverseMut f a -> TraverseMut f a #

min :: TraverseMut f a -> TraverseMut f a -> TraverseMut f a #

Show (f a) => Show (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

Methods

showsPrec :: Int -> TraverseMut f a -> ShowS #

show :: TraverseMut f a -> String #

showList :: [TraverseMut f a] -> ShowS #

Generic (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

type Rep (TraverseMut f a) :: Type -> Type #

Methods

from :: TraverseMut f a -> Rep (TraverseMut f a) x #

to :: Rep (TraverseMut f a) x -> TraverseMut f a #

type HKD (TraverseMut f :: k -> Type) (a :: k) Source # 
Instance details

Defined in Data.Mutable.Class

type HKD (TraverseMut f :: k -> Type) (a :: k) = f a
type Ref s (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

type Ref s (TraverseMut f a) = TraverseRef s (TraverseMut f) a
type Rep (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

type Rep (TraverseMut f a) = D1 ('MetaData "TraverseMut" "Data.Mutable.Class" "mutable-0.2.2.0-inplace" 'True) (C1 ('MetaCons "TraverseMut" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTraverseMut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

newtype Immutable s a Source #

Similar to VarMut, this allows you to overwrite the normal Mutable instance of a type to make it immutable.

For example, let's say you have a type, with the automatically derived generic instance of Mutable:

data MyType = MT
    { mtX :: Int
    , mtY :: Vector Double
    , mtZ :: String
    }
  deriving Generic

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType

This basically uses three mutable references: the Int, the Vector Double, and the String. However, you might want the Mutable instance of MyType to be immutable String field, and so it cannot be updated at all even when thawed. To do that, you can instead have:

data MyType = MT
    { mtX :: Int
    , mtY :: Vector Double
    , mtZ :: Immutable String
    }
  deriving Generic

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType

which has that behavior. The Int and the Vector will be mutable within Ref s MyType, but not the String.

Constructors

Immutable 

Fields

Instances

Instances details
Mutable s (Immutable s a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

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

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

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

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

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

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

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

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

Use an Immutable a as if it were an a

Instance details

Defined in Data.Mutable.Class

Associated Types

type HKD (Immutable s) a #

Methods

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

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

type Ref s (Immutable s a) Source # 
Instance details

Defined in Data.Mutable.Class

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

Defined in Data.Mutable.Class

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

Parts

newtype MutPart s b a Source #

A MutPart s b a is a way to "zoom into" an a, as a part of a mutable reference on b. This allows you to only modify a single a part of the b, without touching the rest. It's spiritually similar to a Lens' b a.

If MutBranch is for sum types, then MutPart is for product types.

See https://mutable.jle.im/05-mutable-parts.html for an introduction to this type.

An example that is commonly found in the ecosystem is something like (flipped) write :: Int -> MVector s a -> a -> m () from Data.Vector.Mutable --- write 3 :: MVector s a -> a -> m (), for instance, lets you modify a specific part of the vector without touching the rest.

You would use a MutPart using freezePart, copyPart, modifyPart, etc.

For non-composite types, there won't really be any meaningful values. However, we have them for many composite types. For example, for tuples:

mutFst :: MutPart s (a, b) a
mutSnd :: MutPart s (a, b) b
ghci> r <- thawRef (2, 4)
ghci> copyPart mutFst r 100
ghci> freezeRef r
(100, 4)

If you are using GRef as an automatically-defined mutable reference, then the easiest way to create these for your mutable types are with fieldMut and posMut.

If you are using the "Higher-kinded data" pattern, then there's an easy way to generate a MutPart for every single field, if you have a product type --- see hkdMutParts for more information.

Constructors

MutPart 

Fields

Instances

Instances details
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z (K1 i (RefFor s c) :: k -> Type) (K1 i (MutPart s (z Identity) c) :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> K1 i (RefFor s c) a) -> K1 i (MutPart s (z Identity) c) a

Category (MutPart s :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

id :: forall (a :: k). MutPart s a a #

(.) :: forall (b :: k) (c :: k) (a :: k). MutPart s b c -> MutPart s a b -> MutPart s a c #

IsoHKD (MutPart s b :: Type -> Type) (a :: Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Associated Types

type HKD (MutPart s b) a #

Methods

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

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

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

Defined in Data.Mutable.Parts

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

withPart Source #

Arguments

:: MutPart s b a

How to zoom into an a from an s

-> Ref s b

The larger reference of s

-> (Ref s a -> m r)

What do do with the smaller sub-reference of a

-> m r 

Using a MutPart, perform a function on a Ref s s as if you had a Ref s a.

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

With a MutPart, read out a specific part of a Ref.

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

With a MutPart, overwrite into a specific part of a Ref.

movePartInto Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutPart s b a 
-> Ref s b

bigger type (destination)

-> Ref s a

smaller type (source)

-> m () 

With a MutPart, copy a Ref containing a subvalue into a specific part of a larger Ref.

data MyType = MT { mtInt :: Int, mtDouble :: Double }
  deriving Generic

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType
ghci> x <- thawRef $ MyType 3 4.5
ghci> y <- thawRef $ 100
ghci> movePartInto (fieldMut #mtInt) x y
ghci> freezeRef x
MyType 100 4.5

movePartOver Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutPart s b a 
-> Ref s a

smaller type (destination)

-> Ref s b

bigger type (source)

-> m () 

With a MutPart, copy a specific part of a larger Ref into a Ref of the smaller subvalue value.

data MyType = MT { mtInt :: Int, mtDouble :: Double }
  deriving Generic

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType
ghci> x <- thawRef $ MyType 3 4.5
ghci> y <- thawRef $ 100
ghci> movePartOver (fieldMut #mtInt) y x
ghci> freezeRef y
3

movePartWithin Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutPart s b a 
-> Ref s b

destination

-> Ref s b

source

-> m () 

With a MutPart, copy a specific part of a large Ref into that same part in another large Ref.

data MyType = MT { mtInt :: Int, mtDouble :: Double }
  deriving Generic

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType
ghci> x <- thawRef $ MyType 3   4.5
ghci> y <- thawRef $ MyType 100 12.34
ghci> movePartWithin (fieldMut #mtInt) x y
ghci> freezeRef x
MyType 100 4.5

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

Clone out a subvalue of a larger Ref.

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

A non-copying version of unsafeFreezeRef that can be more efficient for types where the mutable representation is the same as the immutable one (like Vector).

This is safe as long as you never again modify the mutable reference, since it can potentially directly mutate the frozen value magically.

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

With a MutPart, modify a specific part of a Ref with a pure function.

modifyPart' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> a) -> m () Source #

modifyPart, but forces the result before storing it back in the reference.

updatePart :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> (a, r)) -> m r Source #

updateRef, under a MutPart to only modify a specific part of a Ref.

updatePart' :: (Mutable s a, PrimMonad m, PrimState m ~ s) => MutPart s b a -> Ref s b -> (a -> (a, r)) -> m r Source #

updatePart, but forces the result before storing it back in the reference.

Built-in MutPart

Field

class (Mutable s b, Mutable s a) => FieldMut (fld :: Symbol) s b a | fld b -> a where Source #

Create a MutPart for a field name. Should work for any type with one constructor whose mutable reference is GRef. See fieldMut for usage directions.

Mostly leverages the power of Data.Generics.Product.Fields.

Methods

fieldMut Source #

Arguments

:: Label fld

field label (usually given using OverloadedLabels, @#blah)

-> MutPart s b a 

Create a MutPart for a field name. Should work for any type with one constructor whose mutable reference is GRef.

Is meant to be used with OverloadedLabels:

data MyType = MyType { mtInt :: Int, mtDouble :: Double }
  deriving (Generic, Show)

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType
ghci> r <- thawRef (MyType 3 4.5)
ghci> freezePart (fieldMut #mtInt) r
3
ghci> copyPart (fieldMut #mtDouble) 1.23
ghci> freezeRef r
MyType 3 1.23

However, you can use it without OverloadedLabels by using Label with TypeApplications:

ghci> freezePart (fieldMut (Label @"mtInt")) r
3

This and posMut are the main ways to generate a MutPart for a type whose mutable reference is GRef. Note that because all of the lookups are done at compile-time, fieldMut and posMut have more or less identical performance characteristics.

Instances

Instances details
(Mutable s b, Mutable s a, Ref s b ~ GRef s b, GLens' (HasTotalFieldPSym fld) (GRef_ s (Rep b)) (Ref s a), HasField' fld b a) => FieldMut fld s b a Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

fieldMut :: Label fld -> MutPart s b a Source #

withField Source #

Arguments

:: FieldMut fld s b a 
=> Label fld

field label (usually given using OverloadedLabels, @#blah)

-> Ref s b

Larger record reference

-> (Ref s a -> m r)

What to do with the mutable field

-> m r 

A helpful wrapper over withPart (fieldMut #blah). Create a fieldMut and directly use it.

mutField Source #

Arguments

:: forall fld s b a. FieldMut fld s b a 
=> Label fld

field label (usually given using OverloadedLabels, @#blah)

-> Ref s b

Larger record reference

-> Ref s a

Internal mutable field

A helpful wrapper around getMutPart (fieldMut #blah). Directly use a fieldMut to access a mutable field.

data Label (a :: Symbol) #

Proxy for label type

Constructors

Label 

Instances

Instances details
s ~ s' => IsLabel s (Label s') 
Instance details

Defined in Data.Vinyl.Derived

Methods

fromLabel :: Label s' #

Eq (Label a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

(==) :: Label a -> Label a -> Bool #

(/=) :: Label a -> Label a -> Bool #

Show (Label a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

showsPrec :: Int -> Label a -> ShowS #

show :: Label a -> String #

showList :: [Label a] -> ShowS #

Position

class (Mutable s b, Mutable s a) => PosMut (i :: Nat) s b a | i b -> a where Source #

Create a MutPart for a position in a product type. Should work for any type with one constructor whose mutable reference is GRef. See posMut for usage directions.

Mostly leverages the power of Data.Generics.Product.Positions.

Methods

posMut :: MutPart s b a Source #

Create a MutPart for a position in a product type. Should work for any type with one constructor whose mutable reference is GRef.

Meant to be used with TypeApplications:

data MyType = MyType Int Double
  deriving (Generic, Show)

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType
ghci> r <- thawRef (MyType 3 4.5)
ghci> freezePart (posMut @1) r
3
ghci> copyPart (posMut @2) 1.23
ghci> freezeRef r
MyType 3 1.23

This and fieldMut are the main ways to generate a MutPart for a type whose mutable reference is GRef. Note that because all of the lookups are done at compile-time, posMut and fieldMut have more or less identical performance characteristics.

Instances

Instances details
(Mutable s b, Mutable s a, Ref s b ~ GRef s b, gref ~ Fst (Traverse (GRef_ s (CRep b)) 1), Coercible (GRef_ s (Rep b) ()) (gref ()), GLens' (HasTotalPositionPSym i) gref (Ref s a), HasPosition' i b a) => PosMut i s b a Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

posMut :: MutPart s b a Source #

withPos Source #

Arguments

:: forall i s m b a r. PosMut i s b a 
=> Ref s b

Larger record reference

-> (Ref s a -> m r)

What to do with the mutable field

-> m r 

A helpful wrapper over withPart (posMut @n). Create a posMut and directly use it.

mutPos Source #

Arguments

:: forall i s b a. PosMut i s b a 
=> Ref s b

Larger record reference

-> Ref s a

Internal mutable field

A helpful wrapper around getMutPart (posMut @n). Directly use a posMut to access a mutable field.

Tuple

class (Mutable s b, Mutable s a) => TupleMut s b a | b -> a where Source #

Create a MutPart splitting out a product type into a tuple of refs for every field in that product type. Should work for any type with one constructor whose mutable reference is GRef. See tupleMut for usage directions.

Mostly leverages the power of Data.Generics.Product.HList.

Methods

tupleMut :: MutPart s b a Source #

Create a MutPart splitting out a product type into a tuple of refs for every field in that product type. Should work for any type with one constructor whose mutable reference is GRef.

Probably most easily used using withTuple:

data MyType = MyType Int Double
  deriving (Generic, Show)

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType

Now there is an instance of TupleMut m MyType (Int, Double).

ghci> r <- thawRef (MyType 3 4.5)
ghci> withTuple r $ (rI, rD) -> do
   ..     modifyRef rI negate
   ..     modifyRef rD (* 2)
ghci> freezeRef r
MyType (-3) 9

As can be seen, within the lambda, we can get access to every mutable reference inside a MyType reference.

Performance-wise, this appears to be faster than fieldMut and posMut when using a single reference, but slower if using all references.

Instances

Instances details
(Mutable s b, Mutable s a, Ref s b ~ GRef s b, GIsList (GRef_ s (Rep b)) (GRef_ s (Rep b)) (MapRef s as) (MapRef s as), GIsList (Rep b) (Rep b) as as, ListTuple a a as as, ListTuple c c (MapRef s as) (MapRef s as), Ref s a ~ c) => TupleMut s b a Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

tupleMut :: MutPart s b a Source #

withTuple Source #

Arguments

:: TupleMut s b a 
=> Ref s b

Larger record reference

-> (Ref s a -> m r)

What to do with each mutable field. The Ref s a will be a tuple of every field's ref.

-> m r 

A helpful wrapper over withPart tupleMut. Directly operate on the items in the data type, getting the references as a tuple. See tupleMut for more details on when this should work.

data MyType = MyType Int Double
  deriving (Generic, Show)

instance Mutable s MyType where
    type Ref s MyType = GRef s MyType
ghci> r <- thawRef (MyType 3 4.5)
ghci> withTuple r $ (rI, rD) -> do
   ..     modifyRef rI negate
   ..     modifyRef rD (* 2)
ghci> freezeRef r
MyType (-3) 9

Higher-Kinded Data

hkdMutParts :: forall z s. (Generic (z (RefFor s)), Generic (z (MutPart s (z Identity))), HKDMutParts s z (Rep (z (RefFor s))) (Rep (z (MutPart s (z Identity))))) => z (MutPart s (z Identity)) Source #

If you are using the "higher-kinded data" pattern, a la https://reasonablypolymorphic.com/blog/higher-kinded-data/, and you have the appropriate instance for Ref, then you can use this to generate a MutPart for every field, if you have a type with only one constructor.

data MyTypeF f = MT
     { mtInt    :: f Int
     , mtDouble :: f Double
     }
  deriving Generic

instance Mutable (MyTypeF Identity) where
    type Ref (MyTypeF Identity) = MyTypeF (RefFor m)

mx :: MutPart s (MyTypeF Identity) (Vector Int)
my :: MutPart s (MyTypeF Identity) (Vector Double)
MT mx my = hkdMutParts @MyTypeF
ghci> r <- thawRef (MT 3 4.5)
ghci> freezePart mx r
3
ghci> copyPart (mtDouble (hkdMutParts @MyTypeF)) r 12.3
ghci> freezeRef r
MT 3 12.3

Performance-wise, this is about equivalent to fieldMut and posMut for the most part, so the main advantage would be purely syntactical. If performance is an issue, you should benchmark all the different ways just to be sure. As a general rule, it seems like deep nested accesses are faster with composition of fieldMut and posMut, but immediate shallow access is often faster with hkdMutParts...but this probably does vary on a case-by-case basis.

class (Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z i o Source #

Typeclass used to implement hkdMutParts. See documentation of hkdMutParts for more information.

Minimal complete definition

hkdMutParts_

Instances

Instances details
(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s), TypeError ('Text "Cannot use hkdMutParts for uninhabited types: " :<>: 'ShowType z) :: Constraint) => HKDMutParts s z (V1 :: k -> Type) (V1 :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> V1 a) -> V1 a

(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z (U1 :: k -> Type) (U1 :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> U1 a) -> U1 a

(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s), TypeError ('Text "Cannot use hkdMutParts for sum types: " :<>: 'ShowType z) :: Constraint) => HKDMutParts s z (i :+: i' :: k -> Type) (o :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> (i :+: i') a) -> o a

(HKDMutParts s z i o, HKDMutParts s z i' o') => HKDMutParts s z (i :*: i' :: k -> Type) (o :*: o' :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> (i :*: i') a) -> (o :*: o') a

(Mutable s (z Identity), Ref s (z Identity) ~ z (RefFor s)) => HKDMutParts s z (K1 i (RefFor s c) :: k -> Type) (K1 i (MutPart s (z Identity) c) :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a :: k0). (z (RefFor s) -> K1 i (RefFor s c) a) -> K1 i (MutPart s (z Identity) c) a

HKDMutParts s z i o => HKDMutParts s z (M1 a b i :: k -> Type) (M1 a b o :: k -> Type) Source # 
Instance details

Defined in Data.Mutable.Parts

Methods

hkdMutParts_ :: forall (a0 :: k0). (z (RefFor s) -> M1 a b i a0) -> M1 a b o a0

Other

mutFst :: MutPart s (a, b) a Source #

MutPart into the first field of a tuple reference.

mutSnd :: MutPart s (a, b) b Source #

MutPart into the second field of a tuple reference.

mutRec :: forall a as f rec s. (Ref s (rec f as) ~ rec (RecRef s f) as, RecElem rec a a as as (RIndex a as), RecElemFCtx rec (RecRef s f)) => MutPart s (rec f as) (f a) Source #

A MutPart for a field in a vinyl Rec, automatically generated as the first field with a matching type. This is polymorphic to work over both Rec and ARec.

ghci> r <- thawRef $ [1,2,3] :& [True, False] :& RNil
ghci> modifyPart (mutRec @Bool) r reverse
ghci> freezeRef r
[1,2,3] :& [False, True] :& RNil

coerceRef :: Ref s b ~ CoerceRef s b a => MutPart s b a Source #

A MutPart to get into a CoerceRef.

withCoerceRef :: CoerceRef s b a -> (Ref s a -> m r) -> m r Source #

Handy wrapper over getMutPart coerceRef.

Branches

data MutBranch s b a Source #

A MutBranch s b a represents the information that b could potentially be an a. Similar in spirit to a Prism' b a.

MutBranch s b a means that a is one potential option that b could be in, or that b is a sum type and a is one of the branches/constructors.

See https://mutable.jle.im/06-mutable-branches.html for an introduction to this module.

If MutPart is for product types, then MutBranch is for sum types.

In this case, "branch" means "potential option". For example, the branches of Either are Left and Right.

The simplest way to make these is by using constrMB. For instance, to get the two branches of an Either:

constrMB #_Left   :: MutBranch s (Either a b) a
constrMB #_Right  :: MutBranch s (Either a b) b
ghci> r <- thawRef (Left 10)
ghci> freezeBranch (constrMB #_Left) r
Just 10
ghci> freezeBranch (constrMB #_Right) r
Nothing

It uses OverloadedLabels, but requires an underscore before the constructor name due to limitations in the extension.

One nice way to use these is with withBranch_:

ghci> r <- thawRef (Just 10)
ghci> withBranch_ (constrMB #_Just) $ i ->    -- i is an Int ref
   ..   modifyRef i (+ 1)
ghci> freezeRef r
Just 11
ghci> r <- thawRef Nothing
ghci> withBranch_ (constrMB #_Just) $ i ->    -- i is an Int ref
   ..   modifyRef i (+ 1)
ghci> freezeRef r
Nothing

Perhaps the most useful usage of this abstraction is for recursive data types.

data List a = Nil | Cons a (List a)
  deriving Generic

instance Mutable s a => Mutable s (List a) where
    type Ref s (List a) = GRef s (List a)

GRef s (List a) is now a mutable linked list! Once we make the MutBranch for the nil and cons cases:

nilBranch :: MutBranch s (List a) ()
nilBranch = constrMB #_Nil

consBranch :: MutBranch s (List a) (a, List a)
consBranch = constrMB #_Cons

Here is a function to check if a linked list is currently empty:

isEmpty
    :: (PrimMonad m, Mutable s a)
    => Ref s (List a)
    -> m Bool
isEmpty = hasBranch nilBranch

Here is one to "pop" a mutable linked list, giving us the first value and shifting the rest of the list up.

popStack
    :: (PrimMonad m, Mutable s a)
    => Ref s (List a)
    -> m (Maybe a)
popStack r = do
    c <- projectBranch consBranch r
    case c of
      Nothing      -> pure Nothing
      Just (x, xs) -> do
        moveRef r xs
        Just $ freezeRef x

And here is a function to concatenate a second linked list to the end of a first one.

concatLists
    :: (PrimMonad m, Mutable s a)
    => Ref s (List a)
    -> Ref s (List a)
    -> m ()
concatLists l1 l2 = do
    c <- projectBranch consBranch l1
    case c of
      Nothing      -> moveRef l1 l2
      Just (_, xs) -> concatLists xs l2

Constructors

MutBranch 

Fields

  • projectBranch :: forall m. (PrimMonad m, PrimState m ~ s) => Ref s b -> m (Maybe (Ref s a))

    With a MutBranch, attempt to get the mutable contents of a branch of a mutable s, if possible.

    ghci> r <- thawRef (Left 10)
    ghci> s <- projectBranch (constrMB #_Left) r
    ghci> case s of Just s' -> freezeRef s'
    10
    
    ghci> r <- thawRef (Right True)
    ghci> s <- projectBranch (constrMB #_Left) r
    ghci> case s of Nothing -> "it was Right"
    "it was Right"
    
  • embedBranch :: forall m. (PrimMonad m, PrimState m ~ s) => Ref s a -> m (Ref s b)

    Embed an a ref as a part of a larger s ref. Note that this does not copy or clone: any mutations to the a ref will be reflected in the s ref, as long as the s ref maintains the reference.

    ghci> r <- thawRef 100
    ghci> s <- embedBranch (constMB #_Left) r
    ghci> freezeRef s
    Left 100
    ghci> modifyRef r (+ 1)
    ghci> freezeRef s
    Left 101
    

    Any mutations on s (as long as they keep the same branch) will also affect a:

    ghci> copyRef s (Left 0)
    ghci> freezeRef r
    0
    

    However, "switching branches" on an Either ref will cause it to loose the original reference:

    ghci> copyRef s (Right True)
    ghci> copyRef s (Left 999)
    ghci> freezeRef r
    0
    

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

With a MutBranch, thaw an a into a mutable s on that branch.

ghci> r <- thawBranch (constrMB #_Left) 10
ghci> freezeRef r
Left 10

freezeBranch Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if is s is an a

-> Ref s b

Structure to read out of

-> m (Maybe a) 

With a MutBranch, read out a specific a branch of an s, if it exists.

ghci> r <- thawRef (Left 10)
ghci> freezeBranch (constrMB #_Left) r
Just 10
ghci> freezeBranch (constrMB #_Right) r
Nothing

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

With a MutBranch, overwrite an s as an a, on that branch.

ghci> r <- thawRef (Left 10)
ghci> s <- thawRef 100
ghci> moveBranch (constrMB #_Left) r s
ghci> freezeRef r
Left 100
ghci> t <- thawRef True
ghci> moveBranch (constrMB #_Right) r t
ghci> freezeRef r
Right True

copyBranch Source #

Arguments

:: (Mutable s b, Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if s is an a

-> Ref s b

Structure to write into

-> a

Value to set s to be

-> m () 

With a MutBranch, set s to have the branch a.

ghci> r <- thawRef (Left 10)
ghci> copyBranch (constrMB #_Left) r 5678
ghci> freezeRef r
Left 5678
ghci> copyBranch (constrMB #_Right) r True
ghci> freezeRef r
Right True

cloneBranch Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if s is an a

-> Ref s b

Structure to read out of

-> m (Maybe (Ref s a)) 

With a MutBranch, attempt to clone out a branch of a mutable s, if possible.

ghci> r <- thawRef (Left 10)
ghci> s <- cloneBranch (constrMB #_Left)
ghci> case s of Just s' -> freezeRef s'
10
ghci> r <- thawRef (Right True)
ghci> s <- cloneBranch (constrMB #_Left)
ghci> case s of Nothing -> "it was Right"
"it was Right"

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

Check if an s is currently a certain branch a.

hasn'tBranch :: (PrimMonad m, PrimState m ~ s) => MutBranch s b a -> Ref s b -> m Bool Source #

Check if an s is not currently a certain branch a.

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

A non-copying version of thawBranch that can be more efficient for types where the mutable representation is the same as the immutable one (like Vector).

This is safe as long as you never again use the original pure value, since it can potentially directly mutate it.

unsafeFreezeBranch Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if is s is an a

-> Ref s b

Structure to read out of

-> m (Maybe a) 

A non-copying version of freezeBranch that can be more efficient for types where the mutable representation is the same as the immutable one (like Vector).

This is safe as long as you never again modify the mutable reference, since it can potentially directly mutate the frozen value magically.

withBranch Source #

Arguments

:: (PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if is s is an a

-> Ref s b

Structure to read out of and write into

-> (Ref s a -> m r)

Action to perform on the a branch of s

-> m (Maybe r) 

With a MutBranch, if an s is on the a branch, perform an action on the a reference and overwrite the s with the modified a. Returns the result of the action, if a was found.

ghci> r <- thawRef (Just 10)
ghci> withBranch_ (constrMB #_Just) $ i ->    -- i is an Int ref
   ..   modifyRef i (+ 1)
ghci> freezeRef r
Just 11
ghci> r <- thawRef Nothing
ghci> withBranch_ (constrMB #_Just) $ i ->    -- i is an Int ref
   ..   modifyRef i (+ 1)
ghci> freezeRef r
Nothing

withBranch_ Source #

Arguments

:: (PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if is s is an a

-> Ref s b

Structure to read out of and write into

-> (Ref s a -> m r)

Action to perform on the a branch of s

-> m () 

withBranch, but discarding the returned value.

modifyBranch Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if s is an a

-> Ref s b

Structure to read out of and write into

-> (a -> a)

Pure function modifying a

-> m () 

With a MutBranch, run a pure function over a potential branch a of s. If s is not on that branch, leaves s unchanged.

ghci> r <- thawRef (Just 10)
ghci> modifyBranch (constrMB #_Just) r (+ 1)
ghci> freezeRef r
Just 11
ghci> r <- thawRef Nothing
ghci> modifyBranch (constrMB #_Just) r (+ 1)
ghci> freezeRef r
Nothing

modifyBranch' Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if s is an a

-> Ref s b

Structure to read out of and write into

-> (a -> a)

Pure function modifying a

-> m () 

modifyBranch, but forces the result before storing it back in the reference.

updateBranch Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if s is an a

-> Ref s b

Structure to read out of and write into

-> (a -> (a, r)) 
-> m (Maybe r) 

With a MutBranch, run a pure function over a potential branch a of s. The function returns the updated a and also an output value to observe. If s is not on that branch, leaves s unchanged.

ghci> r <- thawRef (Just 10)
ghci> updateBranch (constrMB #_Just) r $ i -> (i + 1, show i)
Just "10"
ghci> freezeRef r
Just 11
ghci> r <- thawRef Nothing
ghci> updateBranch (constrMB #_Just) r $ i -> (i + 1, show i)
Nothing
ghci> freezeRef r
Nothing

updateBranch' Source #

Arguments

:: (Mutable s a, PrimMonad m, PrimState m ~ s) 
=> MutBranch s b a

How to check if s is an a

-> Ref s b

Structure to read out of and write into

-> (a -> (a, r)) 
-> m (Maybe r) 

updateBranch, but forces the result before storing it back in the reference.

Built-in MutBranch

Using GHC Generics

constrMB :: forall ctor s b a. (Ref s b ~ GRef s b, GMutBranchConstructor ctor s (Rep b) a) => CLabel ctor -> MutBranch s b a Source #

Create a MutBranch for any data type with a Generic instance by specifying the constructor name using OverloadedLabels

ghci> r <- thawRef (Left 10)
ghci> freezeBranch (constrMB #_Left) r
Just 10
ghci> freezeBranch (constrMB #_Right) r
Nothing

Note that due to limitations in OverloadedLabels, you must prefix the constructor name with an undescore.

There also isn't currently any way to utilize OverloadedLabels with operator identifiers, so using it with operator constructors (like : and []) requires explicit TypeApplications:

-- | MutBranch focusing on the cons case of a list
consMB :: (PrimMonad m, Mutable s a) => MutBranch s [a] (a, [a])
consMB = constrMB (CLabel @":")

data CLabel (ctor :: Symbol) Source #

A version of Label that removes an underscore at the beginning when used with -XOverloadedLabels. Used to specify constructors, since labels are currently not able to start with capital letters.

Constructors

CLabel 

Instances

Instances details
ctor_ ~ AppendSymbol "_" ctor => IsLabel ctor_ (CLabel ctor) Source # 
Instance details

Defined in Data.Mutable.Branches

Methods

fromLabel :: CLabel ctor #

class (GMutable s f, Mutable s a) => GMutBranchConstructor (ctor :: Symbol) s f a | ctor f -> a Source #

Typeclass powering constrMB using GHC Generics.

Heavily inspired by Data.Generics.Sum.Constructors.

Minimal complete definition

gmbcProj, gmbcEmbed

Instances

Instances details
(Mutable s a, GMutBranchSum ctor (HasCtorP ctor l) s l r a) => GMutBranchConstructor ctor s (l :+: r) a Source # 
Instance details

Defined in Data.Mutable.Branches

Methods

gmbcProj :: (PrimMonad m, PrimState m ~ s) => CLabel ctor -> GRef_ s (l :+: r) x -> m (Maybe (Ref s a))

gmbcEmbed :: (PrimMonad m, PrimState m ~ s) => CLabel ctor -> Ref s a -> m (GRef_ s (l :+: r) x)

GMutBranchConstructor ctor m f a => GMutBranchConstructor ctor m (M1 D meta f) a Source # 
Instance details

Defined in Data.Mutable.Branches

Methods

gmbcProj :: (PrimMonad m0, PrimState m0 ~ m) => CLabel ctor -> GRef_ m (M1 D meta f) x -> m0 (Maybe (Ref m a))

gmbcEmbed :: (PrimMonad m0, PrimState m0 ~ m) => CLabel ctor -> Ref m a -> m0 (GRef_ m (M1 D meta f) x)

(GMutable s f, Mutable s a, GIsList (GRef_ s f) (GRef_ s f) (MapRef s as) (MapRef s as), GIsList f f as as, ListTuple a a as as, ListRefTuple s b as, Ref s a ~ b) => GMutBranchConstructor ctor s (M1 C ('MetaCons ctor fixity fields) f) a Source # 
Instance details

Defined in Data.Mutable.Branches

Methods

gmbcProj :: (PrimMonad m, PrimState m ~ s) => CLabel ctor -> GRef_ s (M1 C ('MetaCons ctor fixity fields) f) x -> m (Maybe (Ref s a))

gmbcEmbed :: (PrimMonad m, PrimState m ~ s) => CLabel ctor -> Ref s a -> m (GRef_ s (M1 C ('MetaCons ctor fixity fields) f) x)

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 

For common types

nilMB :: Mutable s a => MutBranch s [a] () Source #

MutBranch focusing on the nil case of a list

consMB :: Mutable s a => MutBranch s [a] (a, [a]) Source #

MutBranch focusing on the cons case of a list

nothingMB :: Mutable s a => MutBranch s (Maybe a) () Source #

MutBranch focusing on the Nothing case of a Maybe

justMB :: Mutable s a => MutBranch s (Maybe a) a Source #

MutBranch focusing on the Just case of a Maybe

leftMB :: (Mutable s a, Mutable s b) => MutBranch s (Either a b) a Source #

MutBranch focusing on the Left case of an Either

rightMB :: (Mutable s a, Mutable s b) => MutBranch s (Either a b) b Source #

MutBranch focusing on the Right case of an Either

Re-exports

class Monad m => PrimMonad (m :: Type -> Type) #

Class of monads which can perform primitive state-transformer actions

Minimal complete definition

primitive

Instances

Instances details
PrimMonad IO 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState IO #

Methods

primitive :: (State# (PrimState IO) -> (# State# (PrimState IO), a #)) -> IO a #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) #

Methods

primitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) #

Methods

primitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a #

PrimMonad m => PrimMonad (MaybeT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (MaybeT m) #

Methods

primitive :: (State# (PrimState (MaybeT m)) -> (# State# (PrimState (MaybeT m)), a #)) -> MaybeT m a #

PrimMonad m => PrimMonad (ListT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ListT m) #

Methods

primitive :: (State# (PrimState (ListT m)) -> (# State# (PrimState (ListT m)), a #)) -> ListT m a #

PrimMonad m => PrimMonad (IdentityT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (IdentityT m) #

Methods

primitive :: (State# (PrimState (IdentityT m)) -> (# State# (PrimState (IdentityT m)), a #)) -> IdentityT m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #

(Monoid w, PrimMonad m) => PrimMonad (AccumT w m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (AccumT w m) #

Methods

primitive :: (State# (PrimState (AccumT w m)) -> (# State# (PrimState (AccumT w m)), a #)) -> AccumT w m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #

PrimMonad m => PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (# State# (PrimState (StateT s m)), a #)) -> StateT s m a #

PrimMonad m => PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (# State# (PrimState (StateT s m)), a #)) -> StateT s m a #

PrimMonad m => PrimMonad (SelectT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (SelectT r m) #

Methods

primitive :: (State# (PrimState (SelectT r m)) -> (# State# (PrimState (SelectT r m)), a #)) -> SelectT r m a #

PrimMonad m => PrimMonad (ReaderT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ReaderT r m) #

Methods

primitive :: (State# (PrimState (ReaderT r m)) -> (# State# (PrimState (ReaderT r m)), a #)) -> ReaderT r m a #

PrimMonad m => PrimMonad (ExceptT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ExceptT e m) #

Methods

primitive :: (State# (PrimState (ExceptT e m)) -> (# State# (PrimState (ExceptT e m)), a #)) -> ExceptT e m a #

(Error e, PrimMonad m) => PrimMonad (ErrorT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ErrorT e m) #

Methods

primitive :: (State# (PrimState (ErrorT e m)) -> (# State# (PrimState (ErrorT e m)), a #)) -> ErrorT e m a #

PrimMonad m => PrimMonad (ContT r m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ContT r m) #

Methods

primitive :: (State# (PrimState (ContT r m)) -> (# State# (PrimState (ContT r m)), a #)) -> ContT r m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #

type family PrimState (m :: Type -> Type) #

State token type

Instances

Instances details
type PrimState IO 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ST s) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ST s) = s
type PrimState (ST s) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ST s) = s
type PrimState (MaybeT m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ListT m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (IdentityT m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (WriterT w m) = PrimState m
type PrimState (AccumT w m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (AccumT w m) = PrimState m
type PrimState (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (WriterT w m) = PrimState m
type PrimState (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (WriterT w m) = PrimState m
type PrimState (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (StateT s m) = PrimState m
type PrimState (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (StateT s m) = PrimState m
type PrimState (SelectT r m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (SelectT r m) = PrimState m
type PrimState (ReaderT r m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ReaderT r m) = PrimState m
type PrimState (ExceptT e m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ExceptT e m) = PrimState m
type PrimState (ErrorT e m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ErrorT e m) = PrimState m
type PrimState (ContT r m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ContT r m) = PrimState m
type PrimState (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (RWST r w s m) = PrimState m
type PrimState (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (RWST r w s m) = PrimState m
type PrimState (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (RWST r w s m) = PrimState m