subhask-0.1.1.0: Type safe interface for programming in subcategories of Hask

Safe HaskellNone
LanguageHaskell2010

SubHask.Mutable

Contents

Description

In the SubHask library, every type has both a mutable and immutable version. Normally we work with the immutable version; however, certain algorithms require the mutable version for efficiency. This module defines the interface to the mutable types.

Synopsis

Documentation

data family Mutable m a Source

The mutable version of an immutable data type. This is equivalent to the PrimRef type, which generalizes STRef and IORef.

Unlike PrimRef, Mutable is implemented using a data family. This means that data types can provide more efficient implementations. The canonical example is Vector. Vectors in standard Haskell use a different interface than the standard PrimRef. This requires the programmer learn multiple interfaces, and prevents the programmer from reusing code. Very un-Haskelly. This implementation of mutability gives a consistent interface for all data types.

Instances

(Show a, IsMutable a, PrimBase m) => Show (Mutable m a) Source 
(IsMutable a, PrimBase m, Arbitrary a) => Arbitrary (Mutable m a) Source 
data Mutable m Int = Mutable_ConT_GHC_Types_Int (PrimRef m Int) Source 
data Mutable m Integer = Mutable_ConT_GHC_Integer_Type_Integer (PrimRef m Integer) Source 
data Mutable m Rational = Mutable_ConT_GHC_Real_Rational (PrimRef m Rational) Source 
data Mutable m Float = Mutable_ConT_GHC_Types_Float (PrimRef m Float) Source 
data Mutable m Double = Mutable_ConT_GHC_Types_Double (PrimRef m Double) Source 
data Mutable m Bool = Mutable_ConT_GHC_Types_Bool (PrimRef m Bool) Source 
data Mutable m () = Mutable_TupleT_0 (PrimRef m ()) Source 
data Mutable m POrdering = Mutable_ConT_SubHask_Algebra_POrdering (PrimRef m POrdering) Source 
data Mutable m Ordering = Mutable_ConT_GHC_Types_Ordering (PrimRef m Ordering) Source 
data Mutable m [a0] = Mutable_AppT_ListT__VarT_a_1627457055_ (PrimRef m [a]) Source 
data Mutable m (Maybe a0) = Mutable_AppT__ConT_GHC_Base_Maybe___VarT_a_1627508821_ (PrimRef m (Maybe a)) Source 
data Mutable m (Maybe' a0) = Mutable_AppT__ConT_SubHask_Algebra_Maybe'___VarT_a_1627508936_ (PrimRef m (Maybe' a)) Source 
data Mutable m (WithPreludeOrd a0) = Mutable_WithPreludeOrd (Mutable m a) Source 
data Mutable m (NonNegative t0) = Mutable_NonNegative (Mutable m t) Source 
data Mutable m (VedicSquare n0) = Mutable_VedicSquare (Mutable m (Z n)) Source 
data Mutable m (Ball b0) = Mutable_AppT__ConT_SubHask_Algebra_Metric_Ball___VarT_b_1627656400_ (PrimRef m (Ball b)) Source 
data Mutable m (ZIndex a0) = Mutable_ZIndex (Mutable m (Z (Order a))) Source 
data Mutable m (IO a0) = Mutable_AppT__ConT_GHC_Types_IO___VarT_a_1627710632_ (PrimRef m (IO a)) Source 
data Mutable m (BArray e0) = Mutable_AppT__ConT_SubHask_Algebra_Array_BArray___VarT_e_1627972045_ (PrimRef m (BArray e)) Source 
data Mutable m (UArray e0) = Mutable_AppT__ConT_SubHask_Algebra_Array_UArray___VarT_e_1627973270_ (PrimRef m (UArray e)) Source 
data Mutable m (Forward a0) = Mutable_AppT__ConT_SubHask_Category_Trans_Derivative_Forward___VarT_a_1628012176_ (PrimRef m (Forward a)) Source 
data Mutable m (Box v0) = Mutable_AppT__ConT_SubHask_Algebra_Container_Box___VarT_v_1628020028_ (PrimRef m (Box v)) Source 
data Mutable m (Jaccard a0) = Mutable_Jaccard (Mutable m a) Source 
data Mutable m (Hamming a0) = Mutable_Hamming (Mutable m a) Source 
data Mutable m (Levenshtein a0) = Mutable_Levenshtein (Mutable m a) Source 
data Mutable m (Uncompensated s0) = Mutable_Uncompensated (Mutable m s) Source 
data Mutable m (Lexical a0) = Mutable_Lexical (Mutable m a) Source 
data Mutable m (ComponentWise a0) = Mutable_ComponentWise (Mutable m a) Source 
data Mutable m (Goedel_ r0) = Mutable_Goedel_ (Mutable m r) Source 
data Mutable m (Boolean2Ring b0) = Mutable_Boolean2Ring (Mutable m b) Source 
data Mutable m (Seq a0) = Mutable_AppT__ConT_SubHask_Compatibility_Containers_Seq___VarT_a_1628103216_ (PrimRef m (Seq a)) Source 
data Mutable m (IntMap a0) = Mutable_AppT__ConT_SubHask_Compatibility_Containers_IntMap___VarT_a_1628106664_ (PrimRef m (IntMap a)) Source 
data Mutable m (IntMap' a0) = Mutable_AppT__ConT_SubHask_Compatibility_Containers_IntMap'___VarT_a_1628107561_ (PrimRef m (IntMap' a)) Source 
data Mutable m (Set a0) = Mutable_AppT__ConT_SubHask_Compatibility_Containers_Set___VarT_a_1628108370_ (PrimRef m (Set a)) Source 
data Mutable m (LexSet a0) = Mutable_AppT__ConT_SubHask_Compatibility_Containers_LexSet___VarT_a_1628109321_ (PrimRef m (LexSet a)) Source 
data Mutable m (ByteString a0) = Mutable_AppT__ConT_SubHask_Compatibility_ByteString_ByteString___VarT_a_1628156234_ (PrimRef m (ByteString a)) Source 
data Mutable m (PartitionOnNewline a0) = Mutable_PartitionOnNewline (Mutable m a) Source 
data Mutable m (a0, b0) = Mutable_AppT__AppT__TupleT_2___VarT_a_1627457252____VarT_b_1627457253_ (PrimRef m (a, b)) Source 
data Mutable m (a0 -> b0) = Mutable_AppT__AppT_ArrowT__VarT_a_1627457532____VarT_b_1627457533_ (PrimRef m (a -> b)) Source 
data Mutable m (Any cxt0 x0) = Mutable_AppT__AppT__ConT_SubHask_Algebra_Any___VarT_cxt_1627508297____VarT_x_1627508298_ (PrimRef m (Any cxt x)) Source 
data Mutable m (Labeled' a0 b0) = Mutable_AppT__AppT__ConT_SubHask_Algebra_Labeled'___VarT_a_1627509060____VarT_b_1627509061_ (PrimRef m (Labeled' a b)) Source 
data Mutable m (Galois p0 k0) = Mutable_Galois (Mutable m (Z ((^) p k))) Source 
data Mutable m (Polynomial_ a0 b0) = Mutable_AppT__AppT__ConT_SubHask_Category_Polynomial_Polynomial____VarT_a_1627677154____VarT_b_1627677155_ (PrimRef m (Polynomial_ a b)) Source 
data Mutable m (Either a0 b0) = Mutable_AppT__AppT__ConT_Data_Either_Either___VarT_a_1627710905____VarT_b_1627710906_ (PrimRef m (Either a b)) Source 
data Mutable m ((+>) a0 b0) = Mutable_AppT__AppT__ConT_SubHask_Algebra_Vector______VarT_a_1627758364____VarT_b_1627758365_ (PrimRef m ((+>) a b)) Source 
data Mutable m (BloomFilter n0 a0) = Mutable_AppT__AppT__ConT_SubHask_Compatibility_BloomFilter_BloomFilter___VarT_n_1628101621____VarT_a_1628101622_ (PrimRef m (BloomFilter n a)) Source 
data Mutable m (Map i0 e0) = Mutable_AppT__AppT__ConT_SubHask_Compatibility_Containers_Map___VarT_i_1628104360____VarT_e_1628104361_ (PrimRef m (Map i e)) Source 
data Mutable m (Map' i0 e0) = Mutable_AppT__AppT__ConT_SubHask_Compatibility_Containers_Map'___VarT_i_1628105501____VarT_e_1628105502_ (PrimRef m (Map' i e)) Source 
data Mutable m (a0, b0, c0) = Mutable_AppT__AppT__AppT__TupleT_3___VarT_a_1627457391____VarT_b_1627457392____VarT_c_1627457393_ (PrimRef m (a, b, c)) Source 
data Mutable m ((/) k a0 b0) = Mutable_Mod (Mutable m a) Source 
data Mutable m (ProofOf * Polynomial_ a0) = Mutable_AppT__AppT__ConT_SubHask_Category_ProofOf___ConT_SubHask_Category_Polynomial_Polynomial_____VarT_a_1627677543_ (PrimRef m (ProofOf * Polynomial_ a)) Source 
data Mutable m (IncreasingT cat0 a0 b0) = Mutable_AppT__AppT__AppT__ConT_SubHask_Category_Trans_Monotonic_IncreasingT___VarT_cat_1627694221____VarT_a_1627694222____VarT_b_1627694223_ (PrimRef m (IncreasingT cat a b)) Source 
data Mutable m (ProofOf * (IncreasingT cat0) a0) = Mutable_AppT__AppT__ConT_SubHask_Category_ProofOf___AppT__ConT_SubHask_Category_Trans_Monotonic_IncreasingT___VarT_cat_1627694764_____VarT_a_1627694763_ (PrimRef m (ProofOf * (IncreasingT cat) a)) Source 
data Mutable m (SVector Nat n r) = Mutable_SVector_Nat (ForeignPtr r) Source 
data Mutable m (SVector Symbol n r) = Mutable_SVector (PrimRef m (SVector Symbol n r)) Source 
data Mutable m (UVector Symbol n r) = Mutable_UVector (PrimRef m (UVector Symbol n r)) Source 
data Mutable m (Diff n0 a0 b0) = Mutable_AppT__AppT__AppT__ConT_SubHask_Category_Trans_Derivative_Diff___VarT_n_1628013694____VarT_a_1628013695____VarT_b_1628013696_ (PrimRef m (Diff n a b)) Source 
data Mutable m (HyperLogLog k k1 p0 a0) = Mutable_AppT__AppT__ConT_SubHask_Compatibility_HyperLogLog_HyperLogLog___VarT_p_1628153617____VarT_a_1628153618_ (PrimRef m (HyperLogLog k k p a)) Source 

class IsMutable a where Source

This class implements conversion between mutable and immutable data types. It is the equivalent of the functions provided in Contol.Monad.Primitive, but we use the names of from the Data.Vector interface because they are simpler and more intuitive.

Every data type is an instance of this class using a default implementation based on PrimRefs. We use OverlappingInstances to allow some instances to provide more efficient implementations. We require that any overlapping instance be semantically equivalent to prevent unsafe behavior. The use of OverlappingInstances should only affect you if your creating your own specialized instances of the class. You shouldn't have to do this unless you are very concerned about performance on a complex type.

FIXME: It's disappointing that we still require this class, the Primitive class, and the Storable class. Can these all be unified?

Minimal complete definition

freeze, thaw, write

Methods

freeze :: PrimBase m => Mutable m a -> m a Source

Convert a mutable object into an immutable one. The implementation is guaranteed to copy the object within memory. The overhead is linear with the size of the object.

thaw :: PrimBase m => a -> m (Mutable m a) Source

Convert an immutable object into a mutable one The implementation is guaranteed to copy the object within memory. The overhead is linear with the size of the object.

write :: PrimBase m => Mutable m a -> a -> m () Source

Assigns the value of the mutable variable to the immutable one.

copy :: PrimBase m => Mutable m a -> m (Mutable m a) Source

Return a copy of the mutable object. Changes to the copy do not update in the original, and vice-versa.

unsafeFreeze :: PrimBase m => Mutable m a -> m a Source

Like "freeze", but much faster on some types because the implementation is not required to perform a memory copy.

WARNING: You must not modify the mutable variable after calling unsafeFreeze. This might change the value of the immutable variable. This breaks referential transparency and is very bad.

unsafeThaw :: PrimBase m => a -> m (Mutable m a) Source

Like "thaw", but much faster on some types because the implementation is not required to perform a memory copy.

WARNING: You must not access the immutable variable after calling unsafeThaw. The contents of this variable might have changed arbitrarily. This breaks referential transparency and is very bad.

Instances

IsMutable Bool Source 
IsMutable Double Source 
IsMutable Float Source 
IsMutable Int Source 
IsMutable Integer Source 
IsMutable Rational Source 
IsMutable () Source 
IsMutable POrdering Source 
IsMutable [a] Source 
IsMutable (Maybe' a) Source 
IsMutable a0 => IsMutable (WithPreludeOrd a) Source 
IsMutable t0 => IsMutable (NonNegative t) Source 
IsMutable (VedicSquare n) Source 
IsMutable (Ball b) Source 
IsMutable (Componentwise v) Source 
IsMutable a0 => IsMutable (ZIndex a) Source 
IsMutable (BArray e) Source 
IsMutable (UArray e) Source 
IsMutable (Forward a) Source 
IsMutable (Box v) Source 
IsMutable a0 => IsMutable (Jaccard a) Source 
IsMutable a0 => IsMutable (Hamming a) Source 
IsMutable a0 => IsMutable (Levenshtein a) Source 
IsMutable s0 => IsMutable (Uncompensated s) Source 
IsMutable a0 => IsMutable (Lexical a) Source 
IsMutable a0 => IsMutable (ComponentWise a) Source 
IsMutable r0 => IsMutable (Goedel_ r) Source 
IsMutable b0 => IsMutable (Boolean2Ring b) Source 
IsMutable (Seq a) Source 
IsMutable (IntMap a) Source 
IsMutable (IntMap' a) Source 
IsMutable (Set a) Source 
IsMutable (LexSet a) Source 
IsMutable (ByteString a) Source 
IsMutable a0 => IsMutable (PartitionOnNewline a) Source 
IsMutable (a -> b) Source 
IsMutable (a, b) Source 
IsMutable (Any cxt x) Source 
IsMutable (Labeled' a b) Source 
IsMutable (Galois p k) Source 
IsMutable (Polynomial_ a b) Source 
IsMutable ((+>) a b) Source 
IsMutable (BloomFilter n a) Source 
IsMutable (Map i e) Source 
IsMutable (Map' i e) Source 
IsMutable (a, b, c) Source 
IsMutable (ProofOf * Polynomial_ a) Source 
IsMutable (ProofOf * (IncreasingT cat) a) Source 
IsMutable a0 => IsMutable ((/) k a b) Source 
IsMutable (IncreasingT cat a b) Source 
(KnownNat n, ValidSVector Nat n r) => IsMutable (SVector Nat n r) Source 
ValidSVector Symbol n r => IsMutable (SVector Symbol n r) Source 
Prim r => IsMutable (UVector Symbol n r) Source 
IsMutable (Diff n a b) Source 
IsMutable (HyperLogLog k k p a) Source 

immutable2mutable :: IsMutable a => (a -> b -> a) -> PrimBase m => Mutable m a -> b -> m () Source

A Simple default implementation for mutable operations.

mutable2immutable :: IsMutable a => (forall m. PrimBase m => Mutable m a -> b -> m ()) -> a -> b -> a Source

A Simple default implementation for immutable operations.

unsafeRunMutableProperty :: PrimBase m => m a -> a Source

This function should only be used from within quickcheck properties. All other uses are unsafe.

mkMutable :: Q Type -> Q [Dec] Source

Inspects the given type and creates the most efficient Mutable instance possible.

FIXME: implement properly

Primitive types

class PrimMonad m => PrimBase m

Class of primitive monads for state-transformer actions.

Unlike PrimMonad, this typeclass requires that the Monad be fully expressed as a state transformer, therefore disallowing other monad transformers on top of the base IO or ST.

Minimal complete definition

internal

Instances

type family PrimState m :: *

State token type

Instances

type PrimState IO = RealWorld 
type PrimState (ST s) = s 
type PrimState (IdentityT m) = PrimState m 
type PrimState (ListT m) = PrimState m 
type PrimState (MaybeT m) = PrimState m 
type PrimState (ErrorT e m) = PrimState m 
type PrimState (ReaderT r m) = PrimState m 
type PrimState (StateT s m) = PrimState m 
type PrimState (StateT s m) = PrimState m 
type PrimState (ExceptT e m) = PrimState m 
type PrimState (WriterT w m) = PrimState m 
type PrimState (WriterT w m) = PrimState m 
type PrimState (RWST r w s m) = PrimState m 
type PrimState (RWST r w s m) = PrimState m 

Internal

These exports should never be used directly. They are required by the "mkMutable" TH function.

data PrimRef m a :: (* -> *) -> * -> *

Mutable variable which full analog of IORef or STRef but could use either of the monads. Unfortunately there's no way to convert PrimRef to STRef or IORef.

readPrimRef :: PrimMonad m => PrimRef m a -> m a

Read value of PrimRef.

writePrimRef :: PrimMonad m => PrimRef m a -> a -> m ()

Write value to PrimRef.

newPrimRef :: PrimMonad m => a -> m (PrimRef m a)

Create new mutable variable with initial value a.

helper_liftM :: Monad m => (a -> b) -> m a -> m b Source

We need to export this function for deriving of Monadic functions to work