columbia-0.1.0.2: 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 an inductive data type instance is implemented in readOneLayer. A bare-bones reader function is then let r = readOneLayer proxy r in r. A poly-traversal 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.

Technically, the type of poly-traversals encompasses all co-recursive definitions at that type. Well-founded recursion cannot be guaranteed owing to the cyclical nature of data structures. If one needs recursion to be well-founded, one can use cycReadCompoundData -- the well-foundedness then follows from the finitude of the addresses.

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

RW Bool Source # 
RW Char Source # 
RW Float Source # 
RW Int Source # 
RW Int8 Source # 
RW Int16 Source # 
RW Int32 Source # 
RW Ordering Source # 
RW Word Source # 
RW Word8 Source # 
RW Word16 Source # 
RW Word32 Source # 
RW () Source # 
Typeable * t => RW [t] Source # 
Typeable * t => RW (Maybe t) Source # 
Typeable * t => RW (Set t) Source # 
Typeable1 f => RW (LazyFix f) Source # 
Typeable * t => RW (WithAddress t) Source # 
(Typeable * t, Typeable * u) => RW (Either t u) Source # 
(Typeable * t, Typeable * u) => RW (t, u) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u) Source #

writeData :: Monad m => (t, u) -> ReaderT * (SeekableWriter m Word8) m () Source #

RW (UArray Int32 Int8) Source # 
RW (UArray Int32 Int16) Source # 
RW (UArray Int32 Int32) Source # 
RW (UArray Int32 Word8) Source # 
RW (UArray Int32 Word16) Source # 
RW (UArray Int32 Word32) Source # 
(Typeable * i, Typeable * t) => RW (Array i t) Source # 
(Typeable * t, Typeable * u) => RW (Map t u) Source # 
(Typeable * k, Typeable * v) => RW (Pair k v) Source # 
(Typeable * t, Typeable * u, Typeable * v) => RW (t, u, v) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u, v) Source #

writeData :: Monad m => (t, u, v) -> ReaderT * (SeekableWriter m Word8) m () Source #

(Typeable * t, Typeable * u, Typeable * v, Typeable * w) => RW (t, u, v, w) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u, v, w) Source #

writeData :: Monad m => (t, u, v, w) -> ReaderT * (SeekableWriter m Word8) m () Source #

(Typeable * t, Typeable * u, Typeable * v, Typeable * w, Typeable * x) => RW (t, u, v, w, x) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u, v, w, x) Source #

writeData :: Monad m => (t, u, v, w, x) -> ReaderT * (SeekableWriter m Word8) m () Source #

data RWCtx a Source #

Constructors

RW a => RWCtx 

Instances

RW t => Sat (RWCtx t) Source # 

Methods

dict :: RWCtx t #

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 Word32 Source #

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

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

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

RW Bool Source # 
RW Char Source # 
RW Float Source # 
RW Int Source # 
RW Int8 Source # 
RW Int16 Source # 
RW Int32 Source # 
RW Ordering Source # 
RW Word Source # 
RW Word8 Source # 
RW Word16 Source # 
RW Word32 Source # 
RW () Source # 
Typeable * t => RW [t] Source # 
Typeable * t => RW (Maybe t) Source # 
Typeable * t => RW (Set t) Source # 
Typeable1 f => RW (LazyFix f) Source # 
Typeable * t => RW (WithAddress t) Source # 
(Typeable * t, Typeable * u) => RW (Either t u) Source # 
(Typeable * t, Typeable * u) => RW (t, u) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u) Source #

writeData :: Monad m => (t, u) -> ReaderT * (SeekableWriter m Word8) m () Source #

RW (UArray Int32 Int8) Source # 
RW (UArray Int32 Int16) Source # 
RW (UArray Int32 Int32) Source # 
RW (UArray Int32 Word8) Source # 
RW (UArray Int32 Word16) Source # 
RW (UArray Int32 Word32) Source # 
(Typeable * i, Typeable * t) => RW (Array i t) Source # 
(Typeable * t, Typeable * u) => RW (Map t u) Source # 
(Typeable * k, Typeable * v) => RW (Pair k v) Source # 
(Typeable * t, Typeable * u, Typeable * v) => RW (t, u, v) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u, v) Source #

writeData :: Monad m => (t, u, v) -> ReaderT * (SeekableWriter m Word8) m () Source #

(Typeable * t, Typeable * u, Typeable * v, Typeable * w) => RW (t, u, v, w) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u, v, w) Source #

writeData :: Monad m => (t, u, v, w) -> ReaderT * (SeekableWriter m Word8) m () Source #

(Typeable * t, Typeable * u, Typeable * v, Typeable * w, Typeable * x) => RW (t, u, v, w, x) Source # 

Methods

readData :: Monad m => ReaderT * (SeekableStream m Word8) m (t, u, v, w, x) Source #

writeData :: Monad m => (t, u, v, w, x) -> ReaderT * (SeekableWriter m Word8) m () Source #

data RWCtx a Source #

Constructors

RW a => RWCtx 

Instances

RW t => Sat (RWCtx t) Source # 

Methods

dict :: RWCtx t #

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. Think: the targets have wide appeal, making it easy to find a buyer.

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 Word32) -> d -> ReaderT (SeekableWriter m Word8) m Word32 Source #

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.

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