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

Safe HaskellTrustworthy
LanguageHaskell98

Data.Columbia.Orphans

Contents

Documentation

data LazyFix f Source #

Constructors

LazyFix (Rep f (LazyFix f)) 

Instances

(Sat (ctx (LazyFix f)), Typeable1 f, Data ctx (Rep f (LazyFix f))) => Data ctx (LazyFix f) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> LazyFix f -> w (LazyFix f) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LazyFix f) #

toConstr :: Proxy ctx -> LazyFix f -> Constr #

dataTypeOf :: Proxy ctx -> LazyFix f -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (LazyFix f)) #

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

Eq (Rep f (LazyFix f)) => Eq (LazyFix f) Source # 

Methods

(==) :: LazyFix f -> LazyFix f -> Bool #

(/=) :: LazyFix f -> LazyFix f -> Bool #

Ord (Rep f (LazyFix f)) => Ord (LazyFix f) Source # 

Methods

compare :: LazyFix f -> LazyFix f -> Ordering #

(<) :: LazyFix f -> LazyFix f -> Bool #

(<=) :: LazyFix f -> LazyFix f -> Bool #

(>) :: LazyFix f -> LazyFix f -> Bool #

(>=) :: LazyFix f -> LazyFix f -> Bool #

max :: LazyFix f -> LazyFix f -> LazyFix f #

min :: LazyFix f -> LazyFix f -> LazyFix f #

Read (Rep f (LazyFix f)) => Read (LazyFix f) Source # 
Show (Rep f (LazyFix f)) => Show (LazyFix f) Source # 

Methods

showsPrec :: Int -> LazyFix f -> ShowS #

show :: LazyFix f -> String #

showList :: [LazyFix f] -> ShowS #

Typeable1 f => RW (LazyFix f) Source # 
KeyComparable (LazyFix f) Source # 

Orphan instances

(Data ctx t, Data ctx [Tree t], Sat (ctx (Tree t))) => Data ctx (Tree t) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Tree t -> w (Tree t) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree t) #

toConstr :: Proxy ctx -> Tree t -> Constr #

dataTypeOf :: Proxy ctx -> Tree t -> DataType #

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

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

(Sat (ctx (Fix f)), Typeable1 f, Data ctx (Rep f (Fix f))) => Data ctx (Fix f) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Fix f -> w (Fix f) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Fix f) #

toConstr :: Proxy ctx -> Fix f -> Constr #

dataTypeOf :: Proxy ctx -> Fix f -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Fix f)) #

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

(Sat (ctx (Id x)), Data ctx x) => Data ctx (Id x) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Id x -> w (Id x) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Id x) #

toConstr :: Proxy ctx -> Id x -> Constr #

dataTypeOf :: Proxy ctx -> Id x -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Id x)) #

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

(Ix i, IArray UArray e, Sat (ctx (UArray i e)), Typeable * i, Data ctx e, Sat (ctx [e])) => Data ctx (UArray i e) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> UArray i e -> w (UArray i e) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UArray i e) #

toConstr :: Proxy ctx -> UArray i e -> Constr #

dataTypeOf :: Proxy ctx -> UArray i e -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (UArray i e)) #

dataCast2 :: Typeable2 t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (UArray i e)) #

(Sat (ctx (Const t x)), Data ctx t, Typeable * x) => Data ctx (Const t x) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Const t x -> w (Const t x) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const t x) #

toConstr :: Proxy ctx -> Const t x -> Constr #

dataTypeOf :: Proxy ctx -> Const t x -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Const t x)) #

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

(Sat (ctx ((:@:) g h x)), Typeable1 g, Typeable1 h, Typeable * x, Data ctx (g (h x))) => Data ctx ((:@:) g h x) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall a. a -> w a) -> (g :@: h) x -> w ((g :@: h) x) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((g :@: h) x) #

toConstr :: Proxy ctx -> (g :@: h) x -> Constr #

dataTypeOf :: Proxy ctx -> (g :@: h) x -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w ((g :@: h) x)) #

dataCast2 :: Typeable2 t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w ((g :@: h) x)) #

(Sat (ctx ((:*:) g h x)), Typeable1 g, Typeable1 h, Typeable * x, Data ctx (g x), Data ctx (h x)) => Data ctx ((:*:) g h x) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall a. a -> w a) -> (g :*: h) x -> w ((g :*: h) x) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((g :*: h) x) #

toConstr :: Proxy ctx -> (g :*: h) x -> Constr #

dataTypeOf :: Proxy ctx -> (g :*: h) x -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w ((g :*: h) x)) #

dataCast2 :: Typeable2 t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w ((g :*: h) x)) #

(Sat (ctx ((:+:) g h x)), Typeable1 g, Typeable1 h, Typeable * x, Data ctx (g x), Data ctx (h x)) => Data ctx ((:+:) g h x) Source # 

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall a. a -> w a) -> (g :+: h) x -> w ((g :+: h) x) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((g :+: h) x) #

toConstr :: Proxy ctx -> (g :+: h) x -> Constr #

dataTypeOf :: Proxy ctx -> (g :+: h) x -> DataType #

dataCast1 :: Typeable1 t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w ((g :+: h) x)) #

dataCast2 :: Typeable2 t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w ((g :+: h) x)) #

Eq (Rep f (Fix f)) => Eq (Fix f) Source # 

Methods

(==) :: Fix f -> Fix f -> Bool #

(/=) :: Fix f -> Fix f -> Bool #

Ord (Rep f (Fix f)) => Ord (Fix f) Source # 

Methods

compare :: Fix f -> Fix f -> Ordering #

(<) :: Fix f -> Fix f -> Bool #

(<=) :: Fix f -> Fix f -> Bool #

(>) :: Fix f -> Fix f -> Bool #

(>=) :: Fix f -> Fix f -> Bool #

max :: Fix f -> Fix f -> Fix f #

min :: Fix f -> Fix f -> Fix f #

Typeable1 f => RW (Fix f) Source #