Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensions |
|
Internal module, contains implementation of type aligned real time queues (C.Okasaki 'Purely Functional Data Structures').
Synopsis
- newtype Op (f :: k -> k -> *) (a :: k) (b :: k) = Op {
- runOp :: f b a
- hoistOp :: forall (f :: k -> k -> *) (g :: k -> k -> *) a b. (forall x y. f x y -> g x y) -> Op f a b -> Op g a b
- data ListTr :: (k -> k -> *) -> k -> k -> * where
- liftL :: forall (f :: k -> k -> *) x y. f x y -> ListTr f x y
- foldNatL :: forall (f :: k -> k -> *) c a b. Category c => (forall x y. f x y -> c x y) -> ListTr f a b -> c a b
- lengthListTr :: ListTr f a b -> Int
- foldrL :: forall (f :: k -> k -> *) c a b d. (forall x y z. f y z -> c x y -> c x z) -> c a b -> ListTr f b d -> c a d
- foldlL :: forall (f :: k -> k -> *) c a b d. (forall x y z. c y z -> f x y -> c x z) -> c b d -> ListTr f a b -> c a d
- zipWithL :: forall f g a b a' b'. Category f => (forall x y x' y'. f x y -> f x' y' -> f (g x x') (g y y')) -> ListTr f a b -> ListTr f a' b' -> ListTr f (g a a') (g b b')
- data Queue (f :: k -> k -> *) (a :: k) (b :: k) where
- liftQ :: forall (f :: k -> k -> *) a b. f a b -> Queue f a b
- nilQ :: Queue (f :: k -> k -> *) a a
- consQ :: forall (f :: k -> k -> *) a b c. f b c -> Queue f a b -> Queue f a c
- data ViewL f a b where
- unconsQ :: Queue f a b -> ViewL f a b
- snocQ :: forall (f :: k -> k -> *) a b c. Queue f b c -> f a b -> Queue f a c
- foldNatQ :: forall (f :: k -> k -> *) c a b. Category c => (forall x y. f x y -> c x y) -> Queue f a b -> c a b
- foldrQ :: forall (f :: k -> k -> *) c a b d. (forall x y z. f y z -> c x y -> c x z) -> c a b -> Queue f b d -> c a d
- foldlQ :: forall (f :: k -> k -> *) c a b d. (forall x y z. c y z -> f x y -> c x z) -> c b d -> Queue f a b -> c a d
- hoistQ :: forall (f :: k -> k -> *) (g :: k -> k -> *) a b. (forall x y. f x y -> g x y) -> Queue f a b -> Queue g a b
- zipWithQ :: forall f g a b a' b'. Category f => (forall x y x' y'. f x y -> f x' y' -> f (g x x') (g y y')) -> Queue f a b -> Queue f a' b' -> Queue f (g a a') (g b b')
Documentation
newtype Op (f :: k -> k -> *) (a :: k) (b :: k) Source #
Oposite categoy in which arrows from a
to b
are represented by arrows
from b
to a
in the original category.
hoistOp :: forall (f :: k -> k -> *) (g :: k -> k -> *) a b. (forall x y. f x y -> g x y) -> Op f a b -> Op g a b Source #
Op
is an endo-functor of the category of categories.
data ListTr :: (k -> k -> *) -> k -> k -> * where Source #
Simple representation of a free category by using type aligned lists. This is not a surprise as free monoids can be represented by lists (up to laziness)
ListTr
has
class instance:FreeAlgebra2
liftFree2 @ListTr :: f a b -> ListTr f ab foldNatFree2 @ListTr :: Category d => (forall x y. f x y -> d x y) -> ListTr f a b -> d a b
The same performance concerns that apply to
apply to this encoding of a free category.Free
Note that even though this is a naive version, it behaves quite well in simple benchmarks and quite stable regardless of the level of optimisations.
Instances
foldNatL :: forall (f :: k -> k -> *) c a b. Category c => (forall x y. f x y -> c x y) -> ListTr f a b -> c a b Source #
lengthListTr :: ListTr f a b -> Int Source #
foldrL :: forall (f :: k -> k -> *) c a b d. (forall x y z. f y z -> c x y -> c x z) -> c a b -> ListTr f b d -> c a d Source #
foldlL :: forall (f :: k -> k -> *) c a b d. (forall x y z. c y z -> f x y -> c x z) -> c b d -> ListTr f a b -> c a d Source #
zipWithL :: forall f g a b a' b'. Category f => (forall x y x' y'. f x y -> f x' y' -> f (g x x') (g y y')) -> ListTr f a b -> ListTr f a' b' -> ListTr f (g a a') (g b b') Source #
data Queue (f :: k -> k -> *) (a :: k) (b :: k) where Source #
Type alligned real time queues; Based on `Purely Functinal Data Structures` C.Okasaki. This the most reliably behaved implementation of free categories in this package.
Upper bounds of consQ
, snocQ
, unconsQ
are O(1)
(worst case).
Internal invariant: sum of lengths of two last least is equal the length of the first one.
Instances
foldNatQ :: forall (f :: k -> k -> *) c a b. Category c => (forall x y. f x y -> c x y) -> Queue f a b -> c a b Source #
Efficient fold of a queue into a category, analogous to foldM
.
complexity O(n)
foldrQ :: forall (f :: k -> k -> *) c a b d. (forall x y z. f y z -> c x y -> c x z) -> c a b -> Queue f b d -> c a d Source #
foldlQ :: forall (f :: k -> k -> *) c a b d. (forall x y z. c y z -> f x y -> c x z) -> c b d -> Queue f a b -> c a d Source #