phasechange-0.1: Freezing, thawing, and copy elision

Safe HaskellTrustworthy

Data.PhaseChange

Contents

Description

This module provides referentially transparent functions for working with PhaseChangeable data. For functions that can break referential transparency, see Data.PhaseChange.Unsafe. If you want to write instances, see Data.PhaseChange.Impl.

Synopsis

PhaseChange class

class (Thawed imm ~ mut, Frozen mut ~ imm) => PhaseChange imm mut Source

The PhaseChange class ties together types which provide a mutable and an immutable view on the same data. The mutable type must have a phantom type parameter representing the state thread it is being used in. Many types have this type parameter in the wrong place (not at the end): instances for them can be provided using the M1 and M2 newtypes.

Associated Types

type Thawed imm :: * -> *Source

type Frozen mut :: *Source

Instances

PhaseChange ByteArray MutableByteArray

Data.Primitive.ByteArray

PhaseChange (Array a) (M1 MutableArray a)

Data.Primitive.Array

PhaseChange (Vector a) (M1 MVector a)

Data.Vector

Unbox a => PhaseChange (Vector a) (M1 MVector a)

Data.Vector.Unboxed

Storable a => PhaseChange (Vector a) (M1 MVector a)

Data.Vector.Storable

Prim a => PhaseChange (Vector a) (M1 MVector a)

Data.Vector.Primitive

(Ix i, IArray UArray a, MArray (STUArray S) a (ST S)) => PhaseChange (UArray i a) (M2 STUArray i a)

Data.Array.Unboxed

(Ix i, IArray Array a, MArray (STArray S) a (ST S)) => PhaseChange (Array i a) (M2 STArray i a)

Data.Array

Assymetric constraint synonyms

type Mutable mut = PhaseChange (Frozen mut) mutSource

type Immutable imm = PhaseChange imm (Thawed imm)Source

Functions

thaw :: (Immutable imm, MonadST mST, s ~ World mST) => imm -> mST (Thawed imm s)Source

Get a copy of immutable data in mutable form.

freeze :: (Mutable mut, MonadST mST, s ~ World mST) => mut s -> mST (Frozen mut)Source

Get a copy of mutable data in immutable form.

copy :: (Mutable mut, MonadST mST, s ~ World mST) => mut s -> mST (mut s)Source

Make a copy of mutable data.

frozen :: Mutable mut => (forall s. ST s (mut s)) -> Frozen mutSource

Produce immutable data from a mutating computation. No copies are made.

updateWith :: Mutable mut => (forall s. mut s -> ST s ()) -> Frozen mut -> Frozen mutSource

Make an update of immutable data by applying a mutating action. This function allows for copy elision.

Each chain of updateWiths makes only one copy. A chain of updateWiths on top of a frozen makes no copies.

Newtypes for shifting the 's' type variable to the last position

newtype M1 mut a s Source

Newtype for mutable types whose state thread parameter is in the second-to-last position

Constructors

M1 

Fields

unM1 :: mut s a
 

Instances

PhaseChange (Array a) (M1 MutableArray a)

Data.Primitive.Array

PhaseChange (Vector a) (M1 MVector a)

Data.Vector

Unbox a => PhaseChange (Vector a) (M1 MVector a)

Data.Vector.Unboxed

Storable a => PhaseChange (Vector a) (M1 MVector a)

Data.Vector.Storable

Prim a => PhaseChange (Vector a) (M1 MVector a)

Data.Vector.Primitive

newtype M2 mut a b s Source

Newtype for mutable types whose state thread parameter is in the third-to-last position

Constructors

M2 

Fields

unM2 :: mut s a b
 

Instances

(Ix i, IArray UArray a, MArray (STUArray S) a (ST S)) => PhaseChange (UArray i a) (M2 STUArray i a)

Data.Array.Unboxed

(Ix i, IArray Array a, MArray (STArray S) a (ST S)) => PhaseChange (Array i a) (M2 STArray i a)

Data.Array

Convenience functions for working with M1

thaw1 :: (PhaseChange (imm a) (M1 mut a), MonadST mST, s ~ World mST) => imm a -> mST (mut s a)Source

freeze1 :: (PhaseChange (imm a) (M1 mut a), MonadST mST, s ~ World mST) => mut s a -> mST (imm a)Source

copy1 :: (PhaseChange (imm a) (M1 mut a), MonadST mST, s ~ World mST) => mut s a -> mST (mut s a)Source

frozen1 :: PhaseChange (imm a) (M1 mut a) => (forall s. ST s (mut s a)) -> imm aSource

updateWith1 :: PhaseChange (imm a) (M1 mut a) => (forall s. mut s a -> ST s ()) -> imm a -> imm aSource

Convenience functions for working with M2

thaw2 :: (PhaseChange (imm a b) (M2 mut a b), MonadST mST, s ~ World mST) => imm a b -> mST (mut s a b)Source

freeze2 :: (PhaseChange (imm a b) (M2 mut a b), MonadST mST, s ~ World mST) => mut s a b -> mST (imm a b)Source

copy2 :: (PhaseChange (imm a b) (M2 mut a b), MonadST mST, s ~ World mST) => mut s a b -> mST (mut s a b)Source

frozen2 :: PhaseChange (imm a b) (M2 mut a b) => (forall s. ST s (mut s a b)) -> imm a bSource

updateWith2 :: PhaseChange (imm a b) (M2 mut a b) => (forall s. mut s a b -> ST s ()) -> imm a b -> imm a bSource

A note on Safe Haskell

Much like Data.Typeable, this module provides a class along with functions using it which are safe as long as instances of the class play by the rules. This module is declared Trustworthy, while Data.PhaseChange.Impl is Unsafe, so modules providing instances must necessarily also be Trustworthy (or Unsafe). It is up to the consumer to decide whether modules declaring themselves Trustworthy are actually to be trusted. The combination of any number of Trustworthy modules is safe only as long as all of them are.

A note on GHC

GHC doesn't handle the combination of SPECIALIZE pragmas and type families very well. It appears to be impossible to write them in a way that works with both GHC 7.2 and GHC 7.4. So here the ones for freeze, thaw, etc. work with GHC 7.4 and spit a racket of warnings with 7.2. That's life.