type-combinators-0.2.0.0: A collection of data types for type-level programming

CopyrightCopyright (C) 2015 Kyle Carter
LicenseBSD3
MaintainerKyle Carter <kylcarte@indiana.edu>
Stabilityexperimental
PortabilityRankNTypes
Safe HaskellNone
LanguageHaskell2010

Type.Class.Higher

Description

Higher order analogs of type classes from the Prelude.

Documentation

class Eq1 f where Source

Minimal complete definition

Nothing

Methods

eq1 :: f a -> f a -> Bool Source

neq1 :: f a -> f a -> Bool Source

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 

(=#=) :: Eq1 f => f a -> f a -> Bool infix 4 Source

class Eq2 f where Source

Minimal complete definition

Nothing

Methods

eq2 :: f a b -> f a b -> Bool Source

neq2 :: f a b -> f a b -> Bool Source

(=##=) :: Eq2 f => f a b -> f a b -> Bool infix 4 Source

class Eq3 f where Source

Minimal complete definition

Nothing

Methods

eq3 :: f a b c -> f a b c -> Bool Source

neq3 :: f a b c -> f a b c -> Bool Source

(=###=) :: Eq3 f => f a b c -> f a b c -> Bool infix 4 Source

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

(<=#) :: 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 

class Eq2 f => Ord2 f where Source

Minimal complete definition

Nothing

Methods

compare2 :: f a b -> f a b -> Ordering Source

(<##) :: f a b -> f a b -> Bool infix 4 Source

(>##) :: f a b -> f a b -> Bool infix 4 Source

(<=##) :: f a b -> f a b -> Bool infix 4 Source

(>=##) :: f a b -> f a b -> Bool infix 4 Source

class Eq3 f => Ord3 f where Source

Minimal complete definition

Nothing

Methods

compare3 :: f a b c -> f a b c -> Ordering Source

(<###) :: f a b c -> f a b c -> Bool infix 4 Source

(>###) :: f a b c -> f a b c -> Bool infix 4 Source

(<=###) :: f a b c -> f a b c -> Bool infix 4 Source

(>=###) :: f a b c -> f a b c -> Bool infix 4 Source

class Show1 f where Source

Minimal complete definition

Nothing

Methods

showsPrec1 :: Int -> f a -> ShowS Source

show1 :: f a -> String Source

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 

shows1 :: Show1 f => f a -> ShowS Source

class Show2 f where Source

Minimal complete definition

Nothing

Methods

showsPrec2 :: Int -> f a b -> ShowS Source

show2 :: f a b -> String Source

shows2 :: Show2 f => f a b -> ShowS Source

class Show3 f where Source

Minimal complete definition

Nothing

Methods

showsPrec3 :: Int -> f a b c -> ShowS Source

show3 :: f a b c -> String Source

shows3 :: Show3 f => f a b c -> ShowS Source

class Read1 f where Source

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 

class Read2 f where Source

Methods

readsPrec2 :: Int -> ReadS (Some2 f) Source

Instances

Read2 [k] k (Index k) Source 

class Read3 f where Source

Methods

readsPrec3 :: Int -> ReadS (Some3 f) Source

class Functor1 t where 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 (forall x. f x -> g x) to a natural transformation of (forall mx. Option f mx -> Option g mx).

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

Methods

imap1 :: (forall a. i b a -> f a -> g a) -> t f b -> t g b Source

Instances

IxFunctor1 [k] k (Index k) (Sum k) Source 
IxFunctor1 [k] k (Index k) (Prod k) Source 

class Foldable1 t where Source

Methods

foldMap1 :: Monoid m => (forall a. f a -> m) -> t f b -> m Source

Instances

Foldable1 k k ((:&:) k f) Source 
Foldable1 k k ((:|:) k f) Source 
Foldable1 k (Maybe k) (Option k) Source 
Foldable1 k [k] (Sum k) Source 
Foldable1 k [k] (Prod k) Source 
Foldable1 k ((,) k k) ((:*:) k k f) Source 
Foldable1 k (Either k k) ((:+:) k k f) Source 

class IxFoldable1 i t | t -> i where Source

Methods

ifoldMap1 :: Monoid m => (forall a. i b a -> f a -> m) -> t f b -> m 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

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

Methods

bimap1 :: (forall a. f a -> h a) -> (forall a. g a -> i a) -> t f g b -> t h i b 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

Methods

ibimap1 :: (forall a. i b a -> f a -> f' a) -> (forall a. j b a -> g a -> g' a) -> t f g b -> t f' g' b Source