columbia-0.1.3: Enhanced serialization for media that support seeking.

Safe HaskellTrustworthy
LanguageHaskell98

Data.Columbia.CompoundData

Contents

Description

Serialization of compound data types (with class!). Also read and write methods' type class contexts are implemented with heterogeneous list constraints, making them sufficiently abstract. For every context FooCtx that a program uses, one has a constraint HasField ctx FooCtx, that allows one to find the context evidence in the concrete context.

The recursive function that is generally needed to traverse some data is implemented in readOneLayer. A poly-traversal (aka strategy) is a function that is inserted into this recursive call chain. For instance, cycReadCompoundData is a poly-traversal implementing cycle detection for circular data dependencies, but it leaves the programmer free to determine exactly how the layers are to be read. The types of poly-traversals are found in PolyTraversal and PolyTraversalW.

The library uses a concept of strategy/poly-traversal to coordinate reading. Poly-traversals have as a precondition that they must be seeked at a data entity at address n, an invariant that they must seek to some other data entity before calling each of their parameter operations, and a postcondition that they must leave the stream seeked at n. The operations in Integral, Headers, SeekableStream, and SeekableWriter do not obey these properties; they are low-level implementation functions.

The functions readOneLayer and writeOneLayer do appropriate checking that the data being read is of the correct shape for the type at which they are called. See Headers module for documentation of the data format.

Synopsis

Documentation

class Typeable t => RW t where Source #

The RW class describes operations that can locate entities in a stream by seeking, and also read and write primitive types.

Instances

(Typeable * k, Typeable * v) => RW (Pair k v) Source # 

data RWCtx a Source #

Constructors

RW a => RWCtx 

data LazyFix f Source #

The standard Fix constructor is too strict for some things this library has to do, hence the alias.

Constructors

LazyFix (Rep f (LazyFix f)) 

data LazyMap k v Source #

This type alias exposes an alternate view of the data constructors of a dictionary type. Why break abstraction????because I need the structure sharing.

Instances

(Eq v, Eq k) => Eq (LazyMap k v) Source # 

Methods

(==) :: LazyMap k v -> LazyMap k v -> Bool #

(/=) :: LazyMap k v -> LazyMap k v -> Bool #

(Ord v, Ord k) => Ord (LazyMap k v) Source # 

Methods

compare :: LazyMap k v -> LazyMap k v -> Ordering #

(<) :: LazyMap k v -> LazyMap k v -> Bool #

(<=) :: LazyMap k v -> LazyMap k v -> Bool #

(>) :: LazyMap k v -> LazyMap k v -> Bool #

(>=) :: LazyMap k v -> LazyMap k v -> Bool #

max :: LazyMap k v -> LazyMap k v -> LazyMap k v #

min :: LazyMap k v -> LazyMap k v -> LazyMap k v #

(Show v, Show k) => Show (LazyMap k v) Source # 

Methods

showsPrec :: Int -> LazyMap k v -> ShowS #

show :: LazyMap k v -> String #

showList :: [LazyMap k v] -> ShowS #

readHeader' :: Monad m => ReaderT (SeekableStream m Word8) m Header Source #

A public form of the readHeader function that maintains the pre/postconditions.

Strategy/traversal combinators

(#.) :: Data ctx t => PolyTraversal ctx m t -> (forall t2. Data ctx t2 => PolyTraversal ctx m t2) -> PolyTraversal ctx m t infixl 9 Source #

(##.) :: Data ctx t => PolyTraversalW ctx m t -> (forall t2. Data ctx t2 => PolyTraversalW ctx m t2) -> PolyTraversalW ctx m t infixl 9 Source #

fixT :: Data ctx t => Proxy ctx -> (forall t2. Data ctx t2 => PolyTraversal ctx m t2) -> ReaderT (SeekableStream m Word8) m t Source #

fixTW :: Data ctx t => Proxy ctx -> (forall t2. Data ctx t2 => PolyTraversalW ctx m t2) -> t -> ReaderT (SeekableWriter m Word8) m () Source #

typeCoerce :: (Typeable t, Data ctx t2) => PolyTraversal ctx m t -> PolyTraversal ctx m t2 -> PolyTraversal ctx m t2 Source #

Try to cast from the first traversal; if that fails, use the second traversal.

typeCoerceW :: (Typeable t, Data ctx t2) => PolyTraversalW ctx m t -> PolyTraversalW ctx m t2 -> PolyTraversalW ctx m t2 Source #

Compound data read/write strategies

class Typeable t => RW t where Source #

The RW class describes operations that can locate entities in a stream by seeking, and also read and write primitive types.

Instances

(Typeable * k, Typeable * v) => RW (Pair k v) Source # 

data RWCtx a Source #

Constructors

RW a => RWCtx 

type PolyTraversal ctx m d = Proxy ctx -> (forall a. Data ctx a => ReaderT (SeekableStream m Word8) m a) -> ReaderT (SeekableStream m Word8) m d Source #

A PolyTraversal is a reader method over a data type, parameterized over a method to read components. It can be seen as a curried form of the gmapM operator from Data.Data, in like manner as the Traversal is a curried form of traverse.

readOneLayer :: forall ctx m d. (Monad m, HasField ctx RWCtx, Data ctx d) => PolyTraversal ctx m d Source #

Function returns something PolyTraversal. We can use this to examine the top layer of a data structure, then seek to and read some of its components.

type PolyTraversalW ctx m d = Proxy ctx -> (forall a. Data ctx a => a -> ReaderT (SeekableWriter m Word8) m ()) -> d -> ReaderT (SeekableWriter m Word8) m () Source #

This is a variant of PolyTraversal purposed for writing. By convention, strategies with this type require the stream to be seeked at an *address*, which the strategy will then dereference to access the corresponding data.

writeOneLayer :: forall ctx m d. (Monad m, HasField ctx RWCtx, Data ctx d) => PolyTraversalW ctx m d Source #

Writes the top layer of a data structure, and sells each of the sub-targets in turn.

Seeking and updating

seekByTrack :: (Monad m, Foldable t) => t Int -> ReaderT * (SeekableStream m Word8) m () Source #

This is for traversing several fields in succession. It relies on the notion of track from the zipper package. These tracks are monomorphic; people who want to can define polymorphic tracks in the privacy of their own homes.

seekToField :: forall m. Monad m => Int -> ReaderT (SeekableStream m Word8) m () Source #

seekToField is going to be used to seek at a field by its constructor index, or if it happens to be an array, by its array index.

updateField :: (Monad m, Data ctx d, HasField ctx RWCtx) => Int -> PolyTraversalW ctx (StateT Int m) d Source #

updateField reads and reconstructs the whole constructor (or array) with the specified field as the target of the writer-poly-traversal. It then writes the modified constructor back onto the stream.

updateByTrack :: (Monad m, Data ctx d, HasField ctx RWCtx) => [Int] -> PolyTraversalW ctx m d Source #

updateByTrack is going to modify and reconstruct several constructors in succession.