phasechange-0.1: Freezing, thawing, and copy elision

Safe HaskellUnsafe

Data.PhaseChange.Impl

Description

This module allows you to write instances for PhaseChangeable types. To work with PhaseChangeable data, see Data.PhaseChange. For unsafe functions, see Data.PhaseChange.Unsafe.

Synopsis

Documentation

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

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

Methods

unsafeThawImpl :: imm -> ST s (Thawed imm s)Source

Should return the same data it got as input, viewed as a mutable type, making no changes.

unsafeFreezeImpl :: mut s -> ST s (Frozen mut)Source

Should return the same data it got as input, viewed as an immutable type, making no changes.

copyImpl :: mut s -> ST s (mut s)Source

Should make a perfect copy of the input argument, leaving nothing shared between the original and the copy, and making no other changes.

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

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