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

Safe HaskellTrustworthy
LanguageHaskell98

Data.Columbia.CycleDetection

Contents

Description

These strategies are for cycle detection and construction of fixed points. Cycle detection is used wherever there are cycles in the reference graph implied by a Columbia file, or equivalently, if the file contains indefinitely large data. It ensures that reading and writing operations terminate in the presence of such data. The reconstruction of such data in a reading operation, implies that fixed points will be constructed. That way, while the reading operation terminates, it does construct indefinitely large (non-terminating) data, i.e. it reconstructs the indefinitely large data that was written.

The construction of cycles in the stream representation, is coordinated with the help of types that have non-trivial KeyComparable instances. These types furnish a comparison function, that can be used to compare data structure nodes, and thus detect cycles. These cycles are reflected as reference cycles in a Columbia file. Data at such types, where found in a cycle can be called "loop-breakers." If the data have cycles without loop breakers, the writing process will in fact not terminate, as there is no referentially transparent way (within Haskell) to detect the cycle.

Synopsis

Documentation

class Monad m => StateM m where Source #

Minimal complete definition

mfy'

Associated Types

type StateOf m :: * Source #

Methods

mfy' :: (StateOf m -> (StateOf m, a)) -> m a Source #

Instances

Monad m => StateM (StateT s m) Source # 

Associated Types

type StateOf (StateT s m :: * -> *) :: * Source #

Methods

mfy' :: (StateOf (StateT s m) -> (StateOf (StateT s m), a)) -> StateT s m a Source #

StateM (ReaderT * (IORef s) IO) Source # 

Associated Types

type StateOf (ReaderT * (IORef s) IO :: * -> *) :: * Source #

Methods

mfy' :: (StateOf (ReaderT * (IORef s) IO) -> (StateOf (ReaderT * (IORef s) IO), a)) -> ReaderT * (IORef s) IO a Source #

get' :: StateM m => m (StateOf m) Source #

put' :: StateM m => StateOf m -> m () Source #

cycleDetect :: forall ctx m t. (MonadFix m, StateM m, StateOf m ~ Map Pointer Dynamic, HasField ctx RWCtx, Data ctx t) => PolyTraversal ctx m t Source #

data Pair k v Source #

A Pair is a good data structures for associating a key and a value.

Constructors

Pair k v 

Instances

(Sat (ctx (Pair k v)), Data ctx k, Data ctx v) => Data ctx (Pair k v) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Pair k v -> w (Pair k v) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pair k v) #

toConstr :: Proxy ctx -> Pair k v -> Constr #

dataTypeOf :: Proxy ctx -> Pair k v -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Pair k v)) #

dataCast2 :: Typeable2 t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (Pair k v)) #

ToRep (Pair k) Source # 

Methods

rep :: Pair k x -> Rep (Pair k) x #

fun :: Pair k x -> Ann (Fix (Pair k)) #

val :: Pair k x -> Ann x #

unrep :: Ann (Fix (Pair k)) -> Ann x -> Rep (Pair k) x -> Pair k x #

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

Methods

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

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

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

Methods

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

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

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

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

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

max :: Pair k v -> Pair k v -> Pair k v #

min :: Pair k v -> Pair k v -> Pair k v #

(Read v, Read k) => Read (Pair k v) Source # 

Methods

readsPrec :: Int -> ReadS (Pair k v) #

readList :: ReadS [Pair k v] #

readPrec :: ReadPrec (Pair k v) #

readListPrec :: ReadPrec [Pair k v] #

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

Methods

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

show :: Pair k v -> String #

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

Ord k => KeyComparable (Pair k v) Source # 

Methods

isKeyed :: Pair k v -> Bool Source #

keyCompare :: Pair k v -> Pair k v -> Ordering Source #

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

Orphan instances

KeyComparable Bool Source # 
KeyComparable Char Source # 
KeyComparable Float Source # 
KeyComparable Int Source # 
KeyComparable Int8 Source # 
KeyComparable Int16 Source # 
KeyComparable Int32 Source # 
KeyComparable Int64 Source # 
KeyComparable Ordering Source # 
KeyComparable Word Source # 
KeyComparable Word8 Source # 
KeyComparable Word16 Source # 
KeyComparable Word32 Source # 
KeyComparable Word64 Source # 
KeyComparable () Source # 

Methods

isKeyed :: () -> Bool Source #

keyCompare :: () -> () -> Ordering Source #

Eq (DynamicWithCtx Eq) Source # 
Eq (DynamicWithCtx KeyComparable) Source # 
Ord (DynamicWithCtx KeyComparable) Source # 
KeyComparable t => Sat (KeyCtx t) Source # 

Methods

dict :: KeyCtx t #

KeyComparable [t] Source # 

Methods

isKeyed :: [t] -> Bool Source #

keyCompare :: [t] -> [t] -> Ordering Source #

KeyComparable (Maybe t) Source # 
KeyComparable (Tree t) Source # 

Methods

isKeyed :: Tree t -> Bool Source #

keyCompare :: Tree t -> Tree t -> Ordering Source #

KeyComparable (Id x) Source # 

Methods

isKeyed :: Id x -> Bool Source #

keyCompare :: Id x -> Id x -> Ordering Source #

KeyComparable (Fix f) Source # 

Methods

isKeyed :: Fix f -> Bool Source #

keyCompare :: Fix f -> Fix f -> Ordering Source #

KeyComparable (DynamicWithCtx KeyComparable) Source # 
KeyComparable (Either t t2) Source # 

Methods

isKeyed :: Either t t2 -> Bool Source #

keyCompare :: Either t t2 -> Either t t2 -> Ordering Source #

KeyComparable (t1, t2) Source # 

Methods

isKeyed :: (t1, t2) -> Bool Source #

keyCompare :: (t1, t2) -> (t1, t2) -> Ordering Source #

KeyComparable (UArray i e) Source # 

Methods

isKeyed :: UArray i e -> Bool Source #

keyCompare :: UArray i e -> UArray i e -> Ordering Source #

KeyComparable (Array i e) Source # 

Methods

isKeyed :: Array i e -> Bool Source #

keyCompare :: Array i e -> Array i e -> Ordering Source #

KeyComparable (Map k v) Source # 

Methods

isKeyed :: Map k v -> Bool Source #

keyCompare :: Map k v -> Map k v -> Ordering Source #

KeyComparable (Const x x2) Source # 

Methods

isKeyed :: Const x x2 -> Bool Source #

keyCompare :: Const x x2 -> Const x x2 -> Ordering Source #

KeyComparable (t1, t2, t3) Source # 

Methods

isKeyed :: (t1, t2, t3) -> Bool Source #

keyCompare :: (t1, t2, t3) -> (t1, t2, t3) -> Ordering Source #

KeyComparable ((:+:) f g x) Source # 

Methods

isKeyed :: (f :+: g) x -> Bool Source #

keyCompare :: (f :+: g) x -> (f :+: g) x -> Ordering Source #

KeyComparable ((:*:) f g x) Source # 

Methods

isKeyed :: (f :*: g) x -> Bool Source #

keyCompare :: (f :*: g) x -> (f :*: g) x -> Ordering Source #

KeyComparable ((:@:) f g x) Source # 

Methods

isKeyed :: (f :@: g) x -> Bool Source #

keyCompare :: (f :@: g) x -> (f :@: g) x -> Ordering Source #

KeyComparable (t1, t2, t3, t4) Source # 

Methods

isKeyed :: (t1, t2, t3, t4) -> Bool Source #

keyCompare :: (t1, t2, t3, t4) -> (t1, t2, t3, t4) -> Ordering Source #

KeyComparable (t1, t2, t3, t4, t5) Source # 

Methods

isKeyed :: (t1, t2, t3, t4, t5) -> Bool Source #

keyCompare :: (t1, t2, t3, t4, t5) -> (t1, t2, t3, t4, t5) -> Ordering Source #