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

Safe HaskellTrustworthy
LanguageHaskell98

Data.Columbia.CycleDetection

Description

PolyTraversals that add cycle detection and fixed point construction to any R/W strategy.

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 #

class KeyComparable t where Source #

isKeyed may always return false, but if it returns true ever, keyCompare must be well-defined and a valid equivalence relation on values for which isKeyed returns true (i.e. where all values concerned have isKeyed x=true). The default is to have isKeyed return false on all values.

Methods

isKeyed :: t -> Bool Source #

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

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 #

KeyComparable [t] Source # 

Methods

isKeyed :: [t] -> Bool Source #

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

KeyComparable (Maybe t) Source # 
KeyComparable (Set t) Source # 

Methods

isKeyed :: Set t -> Bool Source #

keyCompare :: Set t -> Set 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 (LazyFix f) Source # 
KeyComparable (WithAddress t) 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 t u) Source # 

Methods

isKeyed :: Map t u -> Bool Source #

keyCompare :: Map t u -> Map t u -> Ordering Source #

KeyComparable (Const x x2) Source # 

Methods

isKeyed :: Const x x2 -> Bool Source #

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

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

Methods

isKeyed :: Pair k v -> Bool Source #

keyCompare :: Pair k v -> Pair k v -> 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 #

data KeyCtx t Source #

Constructors

KeyComparable t => KeyCtx 

Instances

KeyComparable t => Sat (KeyCtx t) Source # 

Methods

dict :: KeyCtx t #

type CycleDetectionW m = StateT (Map (DynamicWithCtx KeyComparable) Word32) m Source #

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

cycleDetectW :: forall ctx m t. (StateM m, StateOf m ~ Map (DynamicWithCtx KeyComparable) Word32, HasField ctx RWCtx, HasField ctx KeyCtx, Data ctx t) => PolyTraversalW 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 #

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

Methods

isKeyed :: Pair k v -> Bool Source #

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

type Rep (Pair k) v Source # 
type Rep (Pair k) v = Pair k v