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

Data.Mutable.Class

Description

Provides the Mutable typeclass and various helpers. See Mutable for the main "entrypoint".

Synopsis

Documentation

class Monad m => Mutable m a where Source #

An instance of Mutable m a means that a can be stored a mutable reference in monad m.

The associated type Ref m 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 m a, Mutable m b) => Mutable m (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 m TwoVectors where
    type Ref m TwoVectors = GRef m TwoVectors

Then now we get:

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

And GRef m 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 m)

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 IO)
ghci> :t is
MVector RealWorld Int
ghci> :t ds
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 m MyType = CoerceRef m 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 m (MyContainer a) = TraverseRef m 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 m a = (v :: Type) | v -> a 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 m (Vector a) = MVector (PrimState m) 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, s ~ PrimState m)
    => Vector a
    -> m (Vector s a)

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

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

This associated type must be unique for a, so no two types a can have the same Ref m 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 m a = GRef m 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 m MyType

-- This is equivalent to the above
instance Mutable m MyType
    type Ref m MyType = MutVar (PrimState m) MyType

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

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

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

type Ref m a = MutVar (PrimState m) a Source #

Methods

thawRef :: a -> m (Ref m 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, s ~ PrimState m)
    => 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 m a (Ref m a) => a -> m (Ref m a) Source #

freezeRef :: Ref m 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, s ~ PrimState m)
    => 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 m a (Ref m a) => Ref m a -> m a Source #

copyRef Source #

Arguments

:: Ref m 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, s ~ PrimState m)
    => 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 m a (Ref m a) => Ref m a -> a -> m () Source #

moveRef Source #

Arguments

:: Ref m a

destination

-> Ref m 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 m a (Ref m a) => Ref m a -> Ref m a -> m () Source #

cloneRef :: Ref m a -> m (Ref m 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 m a (Ref m a) => Ref m a -> m (Ref m a) Source #

unsafeThawRef :: a -> m (Ref m 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 m a (Ref m a) => a -> m (Ref m a) Source #

unsafeFreezeRef :: Ref m 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 m a (Ref m a) => Ref m a -> m a Source #

Instances

Instances details
Monad m => Mutable m () Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: () -> m (Ref m ()) Source #

freezeRef :: Ref m () -> m () Source #

copyRef :: Ref m () -> () -> m () Source #

moveRef :: Ref m () -> Ref m () -> m () Source #

cloneRef :: Ref m () -> m (Ref m ()) Source #

unsafeThawRef :: () -> m (Ref m ()) Source #

unsafeFreezeRef :: Ref m () -> m () Source #

Monad m => Mutable m Void Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Void -> m (Ref m Void) Source #

freezeRef :: Ref m Void -> m Void Source #

copyRef :: Ref m Void -> Void -> m () Source #

moveRef :: Ref m Void -> Ref m Void -> m () Source #

cloneRef :: Ref m Void -> m (Ref m Void) Source #

unsafeThawRef :: Void -> m (Ref m Void) Source #

unsafeFreezeRef :: Ref m Void -> m Void Source #

PrimMonad m => Mutable m ByteArray Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CDouble Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CFloat Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CSUSeconds Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CUSeconds Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CTime Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CClock Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CUIntMax Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CIntMax Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CUIntPtr Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CIntPtr Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CBool Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CULLong Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CLLong Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CSigAtomic Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CWchar Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CSize Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CPtrdiff Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CULong Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CLong Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CUInt Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CInt Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: CInt -> m (Ref m CInt) Source #

freezeRef :: Ref m CInt -> m CInt Source #

copyRef :: Ref m CInt -> CInt -> m () Source #

moveRef :: Ref m CInt -> Ref m CInt -> m () Source #

cloneRef :: Ref m CInt -> m (Ref m CInt) Source #

unsafeThawRef :: CInt -> m (Ref m CInt) Source #

unsafeFreezeRef :: Ref m CInt -> m CInt Source #

PrimMonad m => Mutable m CUShort Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CShort Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CUChar Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CSChar Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m CChar Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Word64 Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Word16 Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Word8 Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Word Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Word -> m (Ref m Word) Source #

freezeRef :: Ref m Word -> m Word Source #

copyRef :: Ref m Word -> Word -> m () Source #

moveRef :: Ref m Word -> Ref m Word -> m () Source #

cloneRef :: Ref m Word -> m (Ref m Word) Source #

unsafeThawRef :: Word -> m (Ref m Word) Source #

unsafeFreezeRef :: Ref m Word -> m Word Source #

PrimMonad m => Mutable m Char Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Char -> m (Ref m Char) Source #

freezeRef :: Ref m Char -> m Char Source #

copyRef :: Ref m Char -> Char -> m () Source #

moveRef :: Ref m Char -> Ref m Char -> m () Source #

cloneRef :: Ref m Char -> m (Ref m Char) Source #

unsafeThawRef :: Char -> m (Ref m Char) Source #

unsafeFreezeRef :: Ref m Char -> m Char Source #

PrimMonad m => Mutable m Bool Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Bool -> m (Ref m Bool) Source #

freezeRef :: Ref m Bool -> m Bool Source #

copyRef :: Ref m Bool -> Bool -> m () Source #

moveRef :: Ref m Bool -> Ref m Bool -> m () Source #

cloneRef :: Ref m Bool -> m (Ref m Bool) Source #

unsafeThawRef :: Bool -> m (Ref m Bool) Source #

unsafeFreezeRef :: Ref m Bool -> m Bool Source #

PrimMonad m => Mutable m Double Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Float Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Natural Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Integer Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m Int Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Int -> m (Ref m Int) Source #

freezeRef :: Ref m Int -> m Int Source #

copyRef :: Ref m Int -> Int -> m () Source #

moveRef :: Ref m Int -> Ref m Int -> m () Source #

cloneRef :: Ref m Int -> m (Ref m Int) Source #

unsafeThawRef :: Int -> m (Ref m Int) Source #

unsafeFreezeRef :: Ref m Int -> m Int Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: HList (a ': as) -> m (Ref m (HList (a ': as))) Source #

freezeRef :: Ref m (HList (a ': as)) -> m (HList (a ': as)) Source #

copyRef :: Ref m (HList (a ': as)) -> HList (a ': as) -> m () Source #

moveRef :: Ref m (HList (a ': as)) -> Ref m (HList (a ': as)) -> m () Source #

cloneRef :: Ref m (HList (a ': as)) -> m (Ref m (HList (a ': as))) Source #

unsafeThawRef :: HList (a ': as) -> m (Ref m (HList (a ': as))) Source #

unsafeFreezeRef :: Ref m (HList (a ': as)) -> m (HList (a ': as)) Source #

Monad m => Mutable m (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: HList '[] -> m (Ref m (HList '[])) Source #

freezeRef :: Ref m (HList '[]) -> m (HList '[]) Source #

copyRef :: Ref m (HList '[]) -> HList '[] -> m () Source #

moveRef :: Ref m (HList '[]) -> Ref m (HList '[]) -> m () Source #

cloneRef :: Ref m (HList '[]) -> m (Ref m (HList '[])) Source #

unsafeThawRef :: HList '[] -> m (Ref m (HList '[])) Source #

unsafeFreezeRef :: Ref m (HList '[]) -> m (HList '[]) Source #

(PrimMonad m, Prim a) => Mutable m (PrimArray a) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: PrimArray a -> m (Ref m (PrimArray a)) Source #

freezeRef :: Ref m (PrimArray a) -> m (PrimArray a) Source #

copyRef :: Ref m (PrimArray a) -> PrimArray a -> m () Source #

moveRef :: Ref m (PrimArray a) -> Ref m (PrimArray a) -> m () Source #

cloneRef :: Ref m (PrimArray a) -> m (Ref m (PrimArray a)) Source #

unsafeThawRef :: PrimArray a -> m (Ref m (PrimArray a)) Source #

unsafeFreezeRef :: Ref m (PrimArray a) -> m (PrimArray a) Source #

PrimMonad m => Mutable m (SmallArray a) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

PrimMonad m => Mutable m (Array a) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Array a -> m (Ref m (Array a)) Source #

freezeRef :: Ref m (Array a) -> m (Array a) Source #

copyRef :: Ref m (Array a) -> Array a -> m () Source #

moveRef :: Ref m (Array a) -> Ref m (Array a) -> m () Source #

cloneRef :: Ref m (Array a) -> m (Ref m (Array a)) Source #

unsafeThawRef :: Array a -> m (Ref m (Array a)) Source #

unsafeFreezeRef :: Ref m (Array a) -> m (Array a) Source #

(PrimMonad m, Prim a) => Mutable m (Vector a) Source #

Mutable reference is MVector.

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Vector a -> m (Ref m (Vector a)) Source #

freezeRef :: Ref m (Vector a) -> m (Vector a) Source #

copyRef :: Ref m (Vector a) -> Vector a -> m () Source #

moveRef :: Ref m (Vector a) -> Ref m (Vector a) -> m () Source #

cloneRef :: Ref m (Vector a) -> m (Ref m (Vector a)) Source #

unsafeThawRef :: Vector a -> m (Ref m (Vector a)) Source #

unsafeFreezeRef :: Ref m (Vector a) -> m (Vector a) Source #

(PrimMonad m, Unbox a) => Mutable m (Vector a) Source #

Mutable reference is MVector.

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Vector a -> m (Ref m (Vector a)) Source #

freezeRef :: Ref m (Vector a) -> m (Vector a) Source #

copyRef :: Ref m (Vector a) -> Vector a -> m () Source #

moveRef :: Ref m (Vector a) -> Ref m (Vector a) -> m () Source #

cloneRef :: Ref m (Vector a) -> m (Ref m (Vector a)) Source #

unsafeThawRef :: Vector a -> m (Ref m (Vector a)) Source #

unsafeFreezeRef :: Ref m (Vector a) -> m (Vector a) Source #

(PrimMonad m, Storable a) => Mutable m (Vector a) Source #

Mutable reference is MVector.

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Vector a -> m (Ref m (Vector a)) Source #

freezeRef :: Ref m (Vector a) -> m (Vector a) Source #

copyRef :: Ref m (Vector a) -> Vector a -> m () Source #

moveRef :: Ref m (Vector a) -> Ref m (Vector a) -> m () Source #

cloneRef :: Ref m (Vector a) -> m (Ref m (Vector a)) Source #

unsafeThawRef :: Vector a -> m (Ref m (Vector a)) Source #

unsafeFreezeRef :: Ref m (Vector a) -> m (Vector a) Source #

PrimMonad m => Mutable m (Vector a) Source #

Mutable reference is MVector.

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Vector a -> m (Ref m (Vector a)) Source #

freezeRef :: Ref m (Vector a) -> m (Vector a) Source #

copyRef :: Ref m (Vector a) -> Vector a -> m () Source #

moveRef :: Ref m (Vector a) -> Ref m (Vector a) -> m () Source #

cloneRef :: Ref m (Vector a) -> m (Ref m (Vector a)) Source #

unsafeThawRef :: Vector a -> m (Ref m (Vector a)) Source #

unsafeFreezeRef :: Ref m (Vector a) -> m (Vector a) Source #

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

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

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Identity a -> m (Ref m (Identity a)) Source #

freezeRef :: Ref m (Identity a) -> m (Identity a) Source #

copyRef :: Ref m (Identity a) -> Identity a -> m () Source #

moveRef :: Ref m (Identity a) -> Ref m (Identity a) -> m () Source #

cloneRef :: Ref m (Identity a) -> m (Ref m (Identity a)) Source #

unsafeThawRef :: Identity a -> m (Ref m (Identity a)) Source #

unsafeFreezeRef :: Ref m (Identity a) -> m (Identity a) Source #

(PrimMonad m, Mutable m a) => Mutable m [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 m [a] = (v :: Type) Source #

Methods

thawRef :: [a] -> m (Ref m [a]) Source #

freezeRef :: Ref m [a] -> m [a] Source #

copyRef :: Ref m [a] -> [a] -> m () Source #

moveRef :: Ref m [a] -> Ref m [a] -> m () Source #

cloneRef :: Ref m [a] -> m (Ref m [a]) Source #

unsafeThawRef :: [a] -> m (Ref m [a]) Source #

unsafeFreezeRef :: Ref m [a] -> m [a] Source #

(Mutable m a, PrimMonad m) => Mutable m (Maybe a) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Maybe a -> m (Ref m (Maybe a)) Source #

freezeRef :: Ref m (Maybe a) -> m (Maybe a) Source #

copyRef :: Ref m (Maybe a) -> Maybe a -> m () Source #

moveRef :: Ref m (Maybe a) -> Ref m (Maybe a) -> m () Source #

cloneRef :: Ref m (Maybe a) -> m (Ref m (Maybe a)) Source #

unsafeThawRef :: Maybe a -> m (Ref m (Maybe a)) Source #

unsafeFreezeRef :: Ref m (Maybe a) -> m (Maybe a) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Dual a -> m (Ref m (Dual a)) Source #

freezeRef :: Ref m (Dual a) -> m (Dual a) Source #

copyRef :: Ref m (Dual a) -> Dual a -> m () Source #

moveRef :: Ref m (Dual a) -> Ref m (Dual a) -> m () Source #

cloneRef :: Ref m (Dual a) -> m (Ref m (Dual a)) Source #

unsafeThawRef :: Dual a -> m (Ref m (Dual a)) Source #

unsafeFreezeRef :: Ref m (Dual a) -> m (Dual a) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Down a -> m (Ref m (Down a)) Source #

freezeRef :: Ref m (Down a) -> m (Down a) Source #

copyRef :: Ref m (Down a) -> Down a -> m () Source #

moveRef :: Ref m (Down a) -> Ref m (Down a) -> m () Source #

cloneRef :: Ref m (Down a) -> m (Ref m (Down a)) Source #

unsafeThawRef :: Down a -> m (Ref m (Down a)) Source #

unsafeFreezeRef :: Ref m (Down a) -> m (Down a) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Sum a -> m (Ref m (Sum a)) Source #

freezeRef :: Ref m (Sum a) -> m (Sum a) Source #

copyRef :: Ref m (Sum a) -> Sum a -> m () Source #

moveRef :: Ref m (Sum a) -> Ref m (Sum a) -> m () Source #

cloneRef :: Ref m (Sum a) -> m (Ref m (Sum a)) Source #

unsafeThawRef :: Sum a -> m (Ref m (Sum a)) Source #

unsafeFreezeRef :: Ref m (Sum a) -> m (Sum a) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Product a -> m (Ref m (Product a)) Source #

freezeRef :: Ref m (Product a) -> m (Product a) Source #

copyRef :: Ref m (Product a) -> Product a -> m () Source #

moveRef :: Ref m (Product a) -> Ref m (Product a) -> m () Source #

cloneRef :: Ref m (Product a) -> m (Ref m (Product a)) Source #

unsafeThawRef :: Product a -> m (Ref m (Product a)) Source #

unsafeFreezeRef :: Ref m (Product a) -> m (Product a) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Identity a -> m (Ref m (Identity a)) Source #

freezeRef :: Ref m (Identity a) -> m (Identity a) Source #

copyRef :: Ref m (Identity a) -> Identity a -> m () Source #

moveRef :: Ref m (Identity a) -> Ref m (Identity a) -> m () Source #

cloneRef :: Ref m (Identity a) -> m (Ref m (Identity a)) Source #

unsafeThawRef :: Identity a -> m (Ref m (Identity a)) Source #

unsafeFreezeRef :: Ref m (Identity a) -> m (Identity a) Source #

PrimMonad m => Mutable m (Complex a) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Complex a -> m (Ref m (Complex a)) Source #

freezeRef :: Ref m (Complex a) -> m (Complex a) Source #

copyRef :: Ref m (Complex a) -> Complex a -> m () Source #

moveRef :: Ref m (Complex a) -> Ref m (Complex a) -> m () Source #

cloneRef :: Ref m (Complex a) -> m (Ref m (Complex a)) Source #

unsafeThawRef :: Complex a -> m (Ref m (Complex a)) Source #

unsafeFreezeRef :: Ref m (Complex a) -> m (Complex a) Source #

PrimMonad m => Mutable m (Ratio a) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Ratio a -> m (Ref m (Ratio a)) Source #

freezeRef :: Ref m (Ratio a) -> m (Ratio a) Source #

copyRef :: Ref m (Ratio a) -> Ratio a -> m () Source #

moveRef :: Ref m (Ratio a) -> Ref m (Ratio a) -> m () Source #

cloneRef :: Ref m (Ratio a) -> m (Ref m (Ratio a)) Source #

unsafeThawRef :: Ratio a -> m (Ref m (Ratio a)) Source #

unsafeFreezeRef :: Ref m (Ratio a) -> m (Ratio a) Source #

Monad m => Mutable m (Immutable a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: Immutable a -> m (Ref m (Immutable a)) Source #

freezeRef :: Ref m (Immutable a) -> m (Immutable a) Source #

copyRef :: Ref m (Immutable a) -> Immutable a -> m () Source #

moveRef :: Ref m (Immutable a) -> Ref m (Immutable a) -> m () Source #

cloneRef :: Ref m (Immutable a) -> m (Ref m (Immutable a)) Source #

unsafeThawRef :: Immutable a -> m (Ref m (Immutable a)) Source #

unsafeFreezeRef :: Ref m (Immutable a) -> m (Immutable a) Source #

PrimMonad m => Mutable m (VarMut a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: VarMut a -> m (Ref m (VarMut a)) Source #

freezeRef :: Ref m (VarMut a) -> m (VarMut a) Source #

copyRef :: Ref m (VarMut a) -> VarMut a -> m () Source #

moveRef :: Ref m (VarMut a) -> Ref m (VarMut a) -> m () Source #

cloneRef :: Ref m (VarMut a) -> m (Ref m (VarMut a)) Source #

unsafeThawRef :: VarMut a -> m (Ref m (VarMut a)) Source #

unsafeFreezeRef :: Ref m (VarMut a) -> m (VarMut a) Source #

Monad m => Mutable m (V1 a) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

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

Methods

thawRef :: V1 a -> m (Ref m (V1 a)) Source #

freezeRef :: Ref m (V1 a) -> m (V1 a) Source #

copyRef :: Ref m (V1 a) -> V1 a -> m () Source #

moveRef :: Ref m (V1 a) -> Ref m (V1 a) -> m () Source #

cloneRef :: Ref m (V1 a) -> m (Ref m (V1 a)) Source #

unsafeThawRef :: V1 a -> m (Ref m (V1 a)) Source #

unsafeFreezeRef :: Ref m (V1 a) -> m (V1 a) Source #

Monad m => Mutable m (U1 a) Source # 
Instance details

Defined in Data.Mutable.Internal

Associated Types

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

Methods

thawRef :: U1 a -> m (Ref m (U1 a)) Source #

freezeRef :: Ref m (U1 a) -> m (U1 a) Source #

copyRef :: Ref m (U1 a) -> U1 a -> m () Source #

moveRef :: Ref m (U1 a) -> Ref m (U1 a) -> m () Source #

cloneRef :: Ref m (U1 a) -> m (Ref m (U1 a)) Source #

unsafeThawRef :: U1 a -> m (Ref m (U1 a)) Source #

unsafeFreezeRef :: Ref m (U1 a) -> m (U1 a) Source #

(Monad m, Mutable m a, Mutable m b) => Mutable m (a, b) Source #

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

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: (a, b) -> m (Ref m (a, b)) Source #

freezeRef :: Ref m (a, b) -> m (a, b) Source #

copyRef :: Ref m (a, b) -> (a, b) -> m () Source #

moveRef :: Ref m (a, b) -> Ref m (a, b) -> m () Source #

cloneRef :: Ref m (a, b) -> m (Ref m (a, b)) Source #

unsafeThawRef :: (a, b) -> m (Ref m (a, b)) Source #

unsafeFreezeRef :: Ref m (a, b) -> m (a, b) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Either a b -> m (Ref m (Either a b)) Source #

freezeRef :: Ref m (Either a b) -> m (Either a b) Source #

copyRef :: Ref m (Either a b) -> Either a b -> m () Source #

moveRef :: Ref m (Either a b) -> Ref m (Either a b) -> m () Source #

cloneRef :: Ref m (Either a b) -> m (Ref m (Either a b)) Source #

unsafeThawRef :: Either a b -> m (Ref m (Either a b)) Source #

unsafeFreezeRef :: Ref m (Either a b) -> m (Either a b) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: ARec f as -> m (Ref m (ARec f as)) Source #

freezeRef :: Ref m (ARec f as) -> m (ARec f as) Source #

copyRef :: Ref m (ARec f as) -> ARec f as -> m () Source #

moveRef :: Ref m (ARec f as) -> Ref m (ARec f as) -> m () Source #

cloneRef :: Ref m (ARec f as) -> m (Ref m (ARec f as)) Source #

unsafeThawRef :: ARec f as -> m (Ref m (ARec f as)) Source #

unsafeFreezeRef :: Ref m (ARec f as) -> m (ARec f as) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Rec f (a2 ': as) -> m (Ref m (Rec f (a2 ': as))) Source #

freezeRef :: Ref m (Rec f (a2 ': as)) -> m (Rec f (a2 ': as)) Source #

copyRef :: Ref m (Rec f (a2 ': as)) -> Rec f (a2 ': as) -> m () Source #

moveRef :: Ref m (Rec f (a2 ': as)) -> Ref m (Rec f (a2 ': as)) -> m () Source #

cloneRef :: Ref m (Rec f (a2 ': as)) -> m (Ref m (Rec f (a2 ': as))) Source #

unsafeThawRef :: Rec f (a2 ': as) -> m (Ref m (Rec f (a2 ': as))) Source #

unsafeFreezeRef :: Ref m (Rec f (a2 ': as)) -> m (Rec f (a2 ': as)) Source #

Monad m => Mutable m (Rec f ('[] :: [u])) Source # 
Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Rec f '[] -> m (Ref m (Rec f '[])) Source #

freezeRef :: Ref m (Rec f '[]) -> m (Rec f '[]) Source #

copyRef :: Ref m (Rec f '[]) -> Rec f '[] -> m () Source #

moveRef :: Ref m (Rec f '[]) -> Ref m (Rec f '[]) -> m () Source #

cloneRef :: Ref m (Rec f '[]) -> m (Ref m (Rec f '[])) Source #

unsafeThawRef :: Rec f '[] -> m (Ref m (Rec f '[])) Source #

unsafeFreezeRef :: Ref m (Rec f '[]) -> m (Rec f '[]) Source #

(Monad m, Mutable m a, Mutable m b, Mutable m c) => Mutable m (a, b, c) Source #

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

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: (a, b, c) -> m (Ref m (a, b, c)) Source #

freezeRef :: Ref m (a, b, c) -> m (a, b, c) Source #

copyRef :: Ref m (a, b, c) -> (a, b, c) -> m () Source #

moveRef :: Ref m (a, b, c) -> Ref m (a, b, c) -> m () Source #

cloneRef :: Ref m (a, b, c) -> m (Ref m (a, b, c)) Source #

unsafeThawRef :: (a, b, c) -> m (Ref m (a, b, c)) Source #

unsafeFreezeRef :: Ref m (a, b, c) -> m (a, b, c) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Const a b -> m (Ref m (Const a b)) Source #

freezeRef :: Ref m (Const a b) -> m (Const a b) Source #

copyRef :: Ref m (Const a b) -> Const a b -> m () Source #

moveRef :: Ref m (Const a b) -> Ref m (Const a b) -> m () Source #

cloneRef :: Ref m (Const a b) -> m (Ref m (Const a b)) Source #

unsafeThawRef :: Const a b -> m (Ref m (Const a b)) Source #

unsafeFreezeRef :: Ref m (Const a b) -> m (Const a b) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Const a b -> m (Ref m (Const a b)) Source #

freezeRef :: Ref m (Const a b) -> m (Const a b) Source #

copyRef :: Ref m (Const a b) -> Const a b -> m () Source #

moveRef :: Ref m (Const a b) -> Ref m (Const a b) -> m () Source #

cloneRef :: Ref m (Const a b) -> m (Ref m (Const a b)) Source #

unsafeThawRef :: Const a b -> m (Ref m (Const a b)) Source #

unsafeFreezeRef :: Ref m (Const a b) -> m (Const a b) Source #

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

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: CoerceMut s a -> m (Ref m (CoerceMut s a)) Source #

freezeRef :: Ref m (CoerceMut s a) -> m (CoerceMut s a) Source #

copyRef :: Ref m (CoerceMut s a) -> CoerceMut s a -> m () Source #

moveRef :: Ref m (CoerceMut s a) -> Ref m (CoerceMut s a) -> m () Source #

cloneRef :: Ref m (CoerceMut s a) -> m (Ref m (CoerceMut s a)) Source #

unsafeThawRef :: CoerceMut s a -> m (Ref m (CoerceMut s a)) Source #

unsafeFreezeRef :: Ref m (CoerceMut s a) -> m (CoerceMut s a) Source #

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

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: TraverseMut f a -> m (Ref m (TraverseMut f a)) Source #

freezeRef :: Ref m (TraverseMut f a) -> m (TraverseMut f a) Source #

copyRef :: Ref m (TraverseMut f a) -> TraverseMut f a -> m () Source #

moveRef :: Ref m (TraverseMut f a) -> Ref m (TraverseMut f a) -> m () Source #

cloneRef :: Ref m (TraverseMut f a) -> m (Ref m (TraverseMut f a)) Source #

unsafeThawRef :: TraverseMut f a -> m (Ref m (TraverseMut f a)) Source #

unsafeFreezeRef :: Ref m (TraverseMut f a) -> m (TraverseMut f a) Source #

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

Defined in Data.Mutable.Internal

Associated Types

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

Methods

thawRef :: (f :+: g) a -> m (Ref m ((f :+: g) a)) Source #

freezeRef :: Ref m ((f :+: g) a) -> m ((f :+: g) a) Source #

copyRef :: Ref m ((f :+: g) a) -> (f :+: g) a -> m () Source #

moveRef :: Ref m ((f :+: g) a) -> Ref m ((f :+: g) a) -> m () Source #

cloneRef :: Ref m ((f :+: g) a) -> m (Ref m ((f :+: g) a)) Source #

unsafeThawRef :: (f :+: g) a -> m (Ref m ((f :+: g) a)) Source #

unsafeFreezeRef :: Ref m ((f :+: g) a) -> m ((f :+: g) a) Source #

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

Defined in Data.Mutable.Internal

Associated Types

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

Methods

thawRef :: (f :*: g) a -> m (Ref m ((f :*: g) a)) Source #

freezeRef :: Ref m ((f :*: g) a) -> m ((f :*: g) a) Source #

copyRef :: Ref m ((f :*: g) a) -> (f :*: g) a -> m () Source #

moveRef :: Ref m ((f :*: g) a) -> Ref m ((f :*: g) a) -> m () Source #

cloneRef :: Ref m ((f :*: g) a) -> m (Ref m ((f :*: g) a)) Source #

unsafeThawRef :: (f :*: g) a -> m (Ref m ((f :*: g) a)) Source #

unsafeFreezeRef :: Ref m ((f :*: g) a) -> m ((f :*: g) a) Source #

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

Defined in Data.Mutable.Internal

Associated Types

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

Methods

thawRef :: K1 i c a -> m (Ref m (K1 i c a)) Source #

freezeRef :: Ref m (K1 i c a) -> m (K1 i c a) Source #

copyRef :: Ref m (K1 i c a) -> K1 i c a -> m () Source #

moveRef :: Ref m (K1 i c a) -> Ref m (K1 i c a) -> m () Source #

cloneRef :: Ref m (K1 i c a) -> m (Ref m (K1 i c a)) Source #

unsafeThawRef :: K1 i c a -> m (Ref m (K1 i c a)) Source #

unsafeFreezeRef :: Ref m (K1 i c a) -> m (K1 i c a) Source #

(Monad m, Mutable m a, Mutable m b, Mutable m c, Mutable m d) => Mutable m (a, b, c, d) Source #

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

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: (a, b, c, d) -> m (Ref m (a, b, c, d)) Source #

freezeRef :: Ref m (a, b, c, d) -> m (a, b, c, d) Source #

copyRef :: Ref m (a, b, c, d) -> (a, b, c, d) -> m () Source #

moveRef :: Ref m (a, b, c, d) -> Ref m (a, b, c, d) -> m () Source #

cloneRef :: Ref m (a, b, c, d) -> m (Ref m (a, b, c, d)) Source #

unsafeThawRef :: (a, b, c, d) -> m (Ref m (a, b, c, d)) Source #

unsafeFreezeRef :: Ref m (a, b, c, d) -> m (a, b, c, d) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Sum f g a -> m (Ref m (Sum f g a)) Source #

freezeRef :: Ref m (Sum f g a) -> m (Sum f g a) Source #

copyRef :: Ref m (Sum f g a) -> Sum f g a -> m () Source #

moveRef :: Ref m (Sum f g a) -> Ref m (Sum f g a) -> m () Source #

cloneRef :: Ref m (Sum f g a) -> m (Ref m (Sum f g a)) Source #

unsafeThawRef :: Sum f g a -> m (Ref m (Sum f g a)) Source #

unsafeFreezeRef :: Ref m (Sum f g a) -> m (Sum f g a) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Product f g a -> m (Ref m (Product f g a)) Source #

freezeRef :: Ref m (Product f g a) -> m (Product f g a) Source #

copyRef :: Ref m (Product f g a) -> Product f g a -> m () Source #

moveRef :: Ref m (Product f g a) -> Ref m (Product f g a) -> m () Source #

cloneRef :: Ref m (Product f g a) -> m (Ref m (Product f g a)) Source #

unsafeThawRef :: Product f g a -> m (Ref m (Product f g a)) Source #

unsafeFreezeRef :: Ref m (Product f g a) -> m (Product f g a) Source #

(Monad m, Mutable m a, Mutable m b, Mutable m c, Mutable m d, Mutable m e) => Mutable m (a, b, c, d, e) Source #

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

Instance details

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: (a, b, c, d, e) -> m (Ref m (a, b, c, d, e)) Source #

freezeRef :: Ref m (a, b, c, d, e) -> m (a, b, c, d, e) Source #

copyRef :: Ref m (a, b, c, d, e) -> (a, b, c, d, e) -> m () Source #

moveRef :: Ref m (a, b, c, d, e) -> Ref m (a, b, c, d, e) -> m () Source #

cloneRef :: Ref m (a, b, c, d, e) -> m (Ref m (a, b, c, d, e)) Source #

unsafeThawRef :: (a, b, c, d, e) -> m (Ref m (a, b, c, d, e)) Source #

unsafeFreezeRef :: Ref m (a, b, c, d, e) -> m (a, b, c, d, e) Source #

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

Defined in Data.Mutable.Instances

Associated Types

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

Methods

thawRef :: Compose f g a -> m (Ref m (Compose f g a)) Source #

freezeRef :: Ref m (Compose f g a) -> m (Compose f g a) Source #

copyRef :: Ref m (Compose f g a) -> Compose f g a -> m () Source #

moveRef :: Ref m (Compose f g a) -> Ref m (Compose f g a) -> m () Source #

cloneRef :: Ref m (Compose f g a) -> m (Ref m (Compose f g a)) Source #

unsafeThawRef :: Compose f g a -> m (Ref m (Compose f g a)) Source #

unsafeFreezeRef :: Ref m (Compose f g a) -> m (Compose f g a) Source #

copyRefWhole Source #

Arguments

:: Mutable m a 
=> Ref m a

destination to overwrite

-> a

pure value

-> m () 

A default implementation of copyRef using thawRef and moveRef.

moveRefWhole Source #

Arguments

:: Mutable m a 
=> Ref m a

destination

-> Ref m a

source

-> m () 

A default implementation of moveRef that round-trips through the pure type, using freezeRef and copyRef. It freezes the entire source and then re-copies it into the destination.

cloneRefWhole :: Mutable m a => Ref m a -> m (Ref m a) Source #

A default implementation of moveRef that round-trips through the pure type, using freezeRef and thawRef. It freezes the entire source and then re-copies it into the destination.

modifyRef :: Mutable m a => Ref m a -> (a -> a) -> m () Source #

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

modifyRef' :: Mutable m a => Ref m a -> (a -> a) -> m () Source #

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

updateRef :: Mutable m a => Ref m 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 m a => Ref m a -> (a -> (a, b)) -> m b Source #

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

modifyRefM :: Mutable m a => Ref m a -> (a -> m a) -> m () Source #

Apply a monadic function on an immutable value onto a value stored in a mutable reference. Uses copyRef into the reference after the action is completed.

modifyRefM' :: Mutable m a => Ref m a -> (a -> m a) -> m () Source #

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

updateRefM :: Mutable m a => Ref m a -> (a -> m (a, b)) -> m b Source #

Apply a monadic function on an immutable value onto a value stored in a mutable reference, returning a result value from that function. Uses copyRef into the reference after the action is completed.

updateRefM' :: Mutable m a => Ref m a -> (a -> m (a, b)) -> m b Source #

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

newtype RefFor m a Source #

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

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

Constructors

RefFor 

Fields

Instances

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

Defined in Data.Mutable.Parts

Methods

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

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

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: z Identity -> m (z (RefFor m)) Source #

defaultFreezeRef :: z (RefFor m) -> m (z Identity) Source #

defaultCopyRef :: z (RefFor m) -> z Identity -> m () Source #

defaultMoveRef :: z (RefFor m) -> z (RefFor m) -> m () Source #

defaultCloneRef :: z (RefFor m) -> m (z (RefFor m)) Source #

defaultUnsafeThawRef :: z Identity -> m (z (RefFor m)) Source #

defaultUnsafeFreezeRef :: z (RefFor m) -> m (z Identity) Source #

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

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

Instance details

Defined in Data.Mutable.Internal

Associated Types

type HKD (RefFor m) a #

Methods

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

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

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

Defined in Data.Mutable.Internal

Methods

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

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

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

Defined in Data.Mutable.Internal

Methods

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

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

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

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

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

max :: RefFor m a -> RefFor m a -> RefFor m a #

min :: RefFor m a -> RefFor m a -> RefFor m a #

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

Defined in Data.Mutable.Internal

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

class DefaultMutable m a r | r -> a where 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 m MyType

-- the above is the same as:
instance Mutable m MyType
    type Ref m MyType = MutVar (PrimState m) MyType

The case for any instance of Generic:

instance Mutable m MyType
    type Ref m MyType = GRef m MyType

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

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

The case for any newtype wrapper:

newtype MyType = MT (Vector Double)

instance Mutable m MyType where
    type Ref m MyType = CoerceRef m 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 m a => Mutable m (MyContainer a) where
    type Ref m (MyContainer a) = TraverseRef m MyContainer a

Methods

defaultThawRef :: a -> m r Source #

defaultFreezeRef :: r -> m a Source #

defaultCopyRef :: r -> a -> m () Source #

defaultMoveRef :: r -> r -> m () Source #

defaultCloneRef :: r -> m r Source #

defaultUnsafeThawRef :: a -> m r Source #

defaultUnsafeFreezeRef :: r -> m a Source #

Instances

Instances details
Applicative m => DefaultMutable m a (ImmutableRef a) Source # 
Instance details

Defined in Data.Mutable.Internal

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

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: a -> m (GRef m a) Source #

defaultFreezeRef :: GRef m a -> m a Source #

defaultCopyRef :: GRef m a -> a -> m () Source #

defaultMoveRef :: GRef m a -> GRef m a -> m () Source #

defaultCloneRef :: GRef m a -> m (GRef m a) Source #

defaultUnsafeThawRef :: a -> m (GRef m a) Source #

defaultUnsafeFreezeRef :: GRef m a -> m a Source #

(PrimMonad m, s ~ PrimState m) => DefaultMutable m a (MutVar s a) Source # 
Instance details

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: a -> m (MutVar s a) Source #

defaultFreezeRef :: MutVar s a -> m a Source #

defaultCopyRef :: MutVar s a -> a -> m () Source #

defaultMoveRef :: MutVar s a -> MutVar s a -> m () Source #

defaultCloneRef :: MutVar s a -> m (MutVar s a) Source #

defaultUnsafeThawRef :: a -> m (MutVar s a) Source #

defaultUnsafeFreezeRef :: MutVar s a -> m a Source #

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

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: s -> m (CoerceRef m s a) Source #

defaultFreezeRef :: CoerceRef m s a -> m s Source #

defaultCopyRef :: CoerceRef m s a -> s -> m () Source #

defaultMoveRef :: CoerceRef m s a -> CoerceRef m s a -> m () Source #

defaultCloneRef :: CoerceRef m s a -> m (CoerceRef m s a) Source #

defaultUnsafeThawRef :: s -> m (CoerceRef m s a) Source #

defaultUnsafeFreezeRef :: CoerceRef m s a -> m s Source #

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

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: z Identity -> m (z (RefFor m)) Source #

defaultFreezeRef :: z (RefFor m) -> m (z Identity) Source #

defaultCopyRef :: z (RefFor m) -> z Identity -> m () Source #

defaultMoveRef :: z (RefFor m) -> z (RefFor m) -> m () Source #

defaultCloneRef :: z (RefFor m) -> m (z (RefFor m)) Source #

defaultUnsafeThawRef :: z Identity -> m (z (RefFor m)) Source #

defaultUnsafeFreezeRef :: z (RefFor m) -> m (z Identity) Source #

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

Defined in Data.Mutable.Internal

Methods

defaultThawRef :: f a -> m (TraverseRef m f a) Source #

defaultFreezeRef :: TraverseRef m f a -> m (f a) Source #

defaultCopyRef :: TraverseRef m f a -> f a -> m () Source #

defaultMoveRef :: TraverseRef m f a -> TraverseRef m f a -> m () Source #

defaultCloneRef :: TraverseRef m f a -> m (TraverseRef m f a) Source #

defaultUnsafeThawRef :: f a -> m (TraverseRef m f a) Source #

defaultUnsafeFreezeRef :: TraverseRef m f a -> m (f a) Source #

Providing and overwriting 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 m MyType where
    type Ref m MyType = GRef m 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
PrimMonad m => Mutable m (VarMut a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: VarMut a -> m (Ref m (VarMut a)) Source #

freezeRef :: Ref m (VarMut a) -> m (VarMut a) Source #

copyRef :: Ref m (VarMut a) -> VarMut a -> m () Source #

moveRef :: Ref m (VarMut a) -> Ref m (VarMut a) -> m () Source #

cloneRef :: Ref m (VarMut a) -> m (Ref m (VarMut a)) Source #

unsafeThawRef :: VarMut a -> m (Ref m (VarMut a)) Source #

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

Defined in Data.Mutable.Class

type Ref m (VarMut a) = MutVar (PrimState m) (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 m DoubleVec where
    type Ref m DoubleVec = CoerceRef m 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 m a, Coercible s a) => Mutable m (CoerceMut s a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: CoerceMut s a -> m (Ref m (CoerceMut s a)) Source #

freezeRef :: Ref m (CoerceMut s a) -> m (CoerceMut s a) Source #

copyRef :: Ref m (CoerceMut s a) -> CoerceMut s a -> m () Source #

moveRef :: Ref m (CoerceMut s a) -> Ref m (CoerceMut s a) -> m () Source #

cloneRef :: Ref m (CoerceMut s a) -> m (Ref m (CoerceMut s a)) Source #

unsafeThawRef :: CoerceMut s a -> m (Ref m (CoerceMut s a)) Source #

unsafeFreezeRef :: Ref m (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 m (CoerceMut s a) Source # 
Instance details

Defined in Data.Mutable.Class

type Ref m (CoerceMut s a) = CoerceRef m (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 m a) => Mutable m (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: TraverseMut f a -> m (Ref m (TraverseMut f a)) Source #

freezeRef :: Ref m (TraverseMut f a) -> m (TraverseMut f a) Source #

copyRef :: Ref m (TraverseMut f a) -> TraverseMut f a -> m () Source #

moveRef :: Ref m (TraverseMut f a) -> Ref m (TraverseMut f a) -> m () Source #

cloneRef :: Ref m (TraverseMut f a) -> m (Ref m (TraverseMut f a)) Source #

unsafeThawRef :: TraverseMut f a -> m (Ref m (TraverseMut f a)) Source #

unsafeFreezeRef :: Ref m (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 m (TraverseMut f a) Source # 
Instance details

Defined in Data.Mutable.Class

type Ref m (TraverseMut f a) = TraverseRef m (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.1.0.1-inplace" 'True) (C1 ('MetaCons "TraverseMut" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTraverseMut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

newtype Immutable 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 m MyType where
    type Ref m MyType = GRef m 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 m MyType where
    type Ref m MyType = GRef m MyType

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

Constructors

Immutable 

Fields

Instances

Instances details
Monad m => Mutable m (Immutable a) Source # 
Instance details

Defined in Data.Mutable.Class

Associated Types

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

Methods

thawRef :: Immutable a -> m (Ref m (Immutable a)) Source #

freezeRef :: Ref m (Immutable a) -> m (Immutable a) Source #

copyRef :: Ref m (Immutable a) -> Immutable a -> m () Source #

moveRef :: Ref m (Immutable a) -> Ref m (Immutable a) -> m () Source #

cloneRef :: Ref m (Immutable a) -> m (Ref m (Immutable a)) Source #

unsafeThawRef :: Immutable a -> m (Ref m (Immutable a)) Source #

unsafeFreezeRef :: Ref m (Immutable a) -> m (Immutable a) Source #

IsoHKD Immutable (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 a #

type Ref m (Immutable a) Source # 
Instance details

Defined in Data.Mutable.Class

type HKD Immutable (a :: Type) Source # 
Instance details

Defined in Data.Mutable.Class

type HKD Immutable (a :: Type) = a

Changing underlying monad

reMutable :: forall m n a r. (Mutable m a, Monad n) => (forall x. m x -> n x) -> (Mutable n a => r) -> r Source #

If you can provice a natural transformation from m to n, you should be able to use a value as if it had Mutable n a if you have Mutable m a.

reMutableConstraint :: forall m n a. (Mutable m a, Monad n) => (forall x. m x -> n x) -> Mutable m a :- Mutable n a Source #

If you can provice a natural transformation from m to n, then Mutable m a should also imply Mutable n a.

Util

type family MapRef m 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 m '[] = '[] 
MapRef m (a ': as) = Ref m a ': MapRef m as