| Copyright | Copyright (C) 2015 Kyle Carter |
|---|---|
| License | BSD3 |
| Maintainer | Kyle Carter <kylcarte@indiana.edu> |
| Stability | experimental |
| Portability | RankNTypes |
| Safe Haskell | None |
| Language | Haskell2010 |
Type.Class.Higher
Description
Higher order analogs of type classes from the Prelude.
Documentation
Minimal complete definition
Nothing
Instances
| Eq1 Symbol Sym Source | |
| Eq1 N Nat Source | |
| Eq1 N Fin Source | |
| Eq1 k (Index k as) Source | |
| Eq2 k k f => Eq1 k (Join k f) Source | |
| Eq r => Eq1 k (C k r) Source | |
| (Eq1 k f, Eq1 k g) => Eq1 k ((:&:) k f g) Source | |
| (Eq1 k f, Eq1 k g) => Eq1 k ((:|:) k f g) Source | |
| Eq1 k1 f => Eq1 k ((:.:) k k f g) Source | |
| Eq1 [k] (Length k) Source | |
| Eq1 k f => Eq1 [k] (Sum k f) Source | |
| Eq1 k f => Eq1 [k] (Prod k f) Source | |
| (Eq1 k f, Eq1 k1 g) => Eq1 (Either k k) ((:+:) k k f g) Source | |
| (Eq1 k f, Eq1 k1 g) => Eq1 ((,) k k) ((:*:) k k f g) Source |
Minimal complete definition
Nothing
Minimal complete definition
Nothing
class Eq1 f => Ord1 f where Source
Minimal complete definition
Nothing
Methods
compare1 :: f a -> f a -> Ordering Source
(<#) :: f a -> f a -> Bool infix 4 Source
(>#) :: f a -> f a -> Bool infix 4 Source
Instances
| Ord1 Symbol Sym Source | |
| Ord1 N Nat Source | |
| Ord1 N Fin Source | |
| Ord1 k (Index k as) Source | |
| Ord2 k k f => Ord1 k (Join k f) Source | |
| Ord r => Ord1 k (C k r) Source | |
| (Ord1 k f, Ord1 k g) => Ord1 k ((:&:) k f g) Source | |
| (Ord1 k f, Ord1 k g) => Ord1 k ((:|:) k f g) Source | |
| Ord1 k1 f => Ord1 k ((:.:) k k f g) Source | |
| Ord1 [k] (Length k) Source | |
| Ord1 k f => Ord1 [k] (Sum k f) Source | |
| Ord1 k f => Ord1 [k] (Prod k f) Source | |
| (Ord1 k f, Ord1 k1 g) => Ord1 (Either k k) ((:+:) k k f g) Source | |
| (Ord1 k f, Ord1 k1 g) => Ord1 ((,) k k) ((:*:) k k f g) Source |
Minimal complete definition
Nothing
Instances
| Show1 Symbol Sym Source | |
| Show1 N Nat Source | |
| Show1 N Fin Source | |
| Show1 k (Index k as) Source | |
| Show2 k k f => Show1 k (Join k f) Source | |
| Show r => Show1 k (C k r) Source | |
| (Show1 k f, Show1 k g) => Show1 k ((:&:) k f g) Source | |
| (Show1 k f, Show1 k g) => Show1 k ((:|:) k f g) Source | |
| Show1 k1 f => Show1 k ((:.:) k k f g) Source | |
| Show1 [k] (Length k) Source | |
| Show1 k f => Show1 [k] (Sum k f) Source | |
| Show1 k f => Show1 [k] (Prod k f) Source | |
| (Show1 k f, Show1 k1 g) => Show1 (Either k k) ((:+:) k k f g) Source | |
| (Show1 k f, Show1 k1 g) => Show1 ((,) k k) ((:*:) k k f g) Source |
Minimal complete definition
Nothing
Minimal complete definition
Nothing
Methods
readsPrec1 :: Int -> ReadS (Some f) Source
Instances
| Read1 N Nat Source | |
| Read1 N Fin Source | |
| Read r => Read1 k (C k r) Source | |
| (Read1 k f, Read1 k g) => Read1 k ((:|:) k f g) Source | |
| Read1 [k] (Length k) Source | |
| Read1 k f => Read1 [k] (Sum k f) Source | |
| Read1 k f => Read1 [k] (Prod k f) Source | |
| Read2 k k1 p => Read1 ((,) k k) (Uncur k k p) Source | |
| (Read1 k f, Read1 k1 g) => Read1 (Either k k) ((:+:) k k f g) Source | |
| Read3 k k1 k2 p => Read1 ((,,) k k k) (Uncur3 k k k p) Source |
Methods
readsPrec2 :: Int -> ReadS (Some2 f) Source
Methods
map1 :: (forall a. f a -> g a) -> t f b -> t g b Source
Take a natural transformation to a lifted natural transformation.
Instances
| Functor1 k k ((:&:) k f) Source | |
| Functor1 k k ((:|:) k f) Source | |
| Functor1 k (Maybe k) (Option k) Source | We can take a natural transformation of |
| Functor1 k [k] (Sum k) Source | |
| Functor1 k [k] (Prod k) Source | |
| Functor1 k ((,) k k) ((:*:) k k f) Source | |
| Functor1 k (Either k k) ((:+:) k k f) Source |
class IxFunctor1 i t | t -> i where Source
Instances
| IxFunctor1 [k] k (Index k) (Sum k) Source | |
| IxFunctor1 [k] k (Index k) (Prod k) Source |
class IxFoldable1 i t | t -> i where Source
Instances
| IxFoldable1 [k] k (Index k) (Sum k) Source | |
| IxFoldable1 [k] k (Index k) (Prod k) Source |
class (Functor1 t, Foldable1 t) => Traversable1 t where Source
Methods
traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source
Instances
| Traversable1 k k ((:&:) k f) Source | |
| Traversable1 k k ((:|:) k f) Source | |
| Traversable1 k (Maybe k) (Option k) Source | |
| Traversable1 k [k] (Sum k) Source | |
| Traversable1 k [k] (Prod k) Source | |
| Traversable1 k ((,) k k) ((:*:) k k f) Source | |
| Traversable1 k (Either k k) ((:+:) k k f) Source |
class (IxFunctor1 i t, IxFoldable1 i t) => IxTraversable1 i t | t -> i where Source
Methods
itraverse1 :: Applicative h => (forall a. i b a -> f a -> h (g a)) -> t f b -> h (t g b) Source
Instances
| IxTraversable1 [k] k (Index k) (Sum k) Source | |
| IxTraversable1 [k] k (Index k) (Prod k) Source |
class Bifunctor1 t where Source
Instances
| Bifunctor1 k k k ((:&:) k) Source | |
| Bifunctor1 k k k ((:|:) k) Source | |
| Bifunctor1 k k ((,) k k) ((:*:) k k) Source | |
| Bifunctor1 k k (Either k k) ((:+:) k k) Source |
class IxBifunctor1 i j t | t -> i j where Source