type-combinators-0.2.4.3: 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, and quantifier data types.

Synopsis

Documentation

class Eq1 f where Source #

Methods

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

eq1 :: Eq (f a) => f a -> f a -> Bool Source #

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

Instances

Eq1 Bool Boolean Source # 

Methods

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

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

Eq1 N Nat Source # 

Methods

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

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

Eq1 N Fin Source # 

Methods

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

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

Eq1 N (IFin x) Source # 

Methods

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

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

Eq2 k k f => Eq1 k (Join k f) Source # 

Methods

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

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

Eq r => Eq1 k (C k r) Source # 

Methods

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

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

Eq1 k (Index k as) Source # 

Methods

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

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

(Eq1 k f, Eq1 k g) => Eq1 k ((:&:) k f g) Source # 

Methods

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

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

(Eq1 k f, Eq1 k g) => Eq1 k ((:|:) k f g) Source # 

Methods

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

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

Eq1 l f => Eq1 k ((:.:) k l f g) Source # 

Methods

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

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

Eq1 [k] (Length k) Source # 

Methods

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

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

Eq1 k f => Eq1 [k] (Sum k f) Source # 

Methods

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

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

Eq1 k f => Eq1 [k] (Prod k f) Source # 

Methods

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

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

Eq1 [k] (Remove k as a) Source # 

Methods

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

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

(Eq1 k f, Eq1 l g) => Eq1 (Either k l) ((:+:) l k f g) Source # 

Methods

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

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

(Eq1 k f, Eq1 l g) => Eq1 (k, l) ((:*:) l k f g) Source # 

Methods

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

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

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

class Eq2 f where Source #

Methods

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

eq2 :: Eq (f a b) => f a b -> f a b -> Bool Source #

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

Instances

Eq2 N N IFin Source # 

Methods

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

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

Eq2 [k] k (Remove k as) Source # 

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 #

Methods

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

eq3 :: Eq (f a b c) => f a b c -> f a b c -> Bool Source #

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

Instances

Eq3 [l] l [l] (Remove l) Source # 

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 #

Methods

compare1 :: f a -> f a -> Ordering Source #

compare1 :: Ord (f a) => 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 Bool Boolean Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 N Nat Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 N Fin Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 N (IFin x) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord2 k k f => Ord1 k (Join k f) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord r => Ord1 k (C k r) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 k (Index k as) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

(Ord1 k f, Ord1 k g) => Ord1 k ((:&:) k f g) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

(Ord1 k f, Ord1 k g) => Ord1 k ((:|:) k f g) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 l f => Ord1 k ((:.:) k l f g) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 [k] (Length k) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 k f => Ord1 [k] (Sum k f) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 k f => Ord1 [k] (Prod k f) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

Ord1 [k] (Remove k as a) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

(Ord1 k f, Ord1 l g) => Ord1 (Either k l) ((:+:) l k f g) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

(Ord1 k f, Ord1 l g) => Ord1 (k, l) ((:*:) l k f g) Source # 

Methods

compare1 :: f a -> f a -> Ordering Source #

(<#) :: f a -> f a -> Bool Source #

(>#) :: f a -> f a -> Bool Source #

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

(>=#) :: f a -> f a -> Bool Source #

class Eq2 f => Ord2 f where Source #

Methods

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

compare2 :: Ord (f a b) => 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 #

Instances

Ord2 N N IFin Source # 

Methods

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

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

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

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

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

Ord2 [k] k (Remove k as) Source # 

Methods

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

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

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

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

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

class Eq3 f => Ord3 f where Source #

Methods

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

compare3 :: Ord (f a b c) => 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 #

Instances

Ord3 [l] l [l] (Remove l) Source # 

Methods

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

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

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

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

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

class Show1 f where Source #

Methods

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

showsPrec1 :: Show (f a) => Int -> f a -> ShowS Source #

show1 :: f a -> String Source #

Instances

Show1 Bool Boolean Source # 

Methods

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

show1 :: f a -> String Source #

Show1 N Nat Source # 

Methods

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

show1 :: f a -> String Source #

Show1 N Fin Source # 

Methods

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

show1 :: f a -> String Source #

Show1 N (IFin x) Source # 

Methods

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

show1 :: f a -> String Source #

Show2 k k f => Show1 k (Join k f) Source # 

Methods

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

show1 :: f a -> String Source #

Show r => Show1 k (C k r) Source # 

Methods

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

show1 :: f a -> String Source #

Show1 k (Index k as) Source # 

Methods

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

show1 :: f a -> String Source #

(Show1 k f, Show1 k g) => Show1 k ((:&:) k f g) Source # 

Methods

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

show1 :: f a -> String Source #

(Show1 k f, Show1 k g) => Show1 k ((:|:) k f g) Source # 

Methods

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

show1 :: f a -> String Source #

Show1 l f => Show1 k ((:.:) k l f g) Source # 

Methods

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

show1 :: f a -> String Source #

Show1 [k] (Length k) Source # 

Methods

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

show1 :: f a -> String Source #

Show1 k f => Show1 [k] (Sum k f) Source # 

Methods

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

show1 :: f a -> String Source #

Show1 k f => Show1 [k] (Prod k f) Source # 

Methods

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

show1 :: f a -> String Source #

Show1 [k] (Remove k as a) Source # 

Methods

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

show1 :: f a -> String Source #

(Show1 k f, Show1 l g) => Show1 (Either k l) ((:+:) l k f g) Source # 

Methods

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

show1 :: f a -> String Source #

(Show1 k f, Show1 l g) => Show1 (k, l) ((:*:) l k f g) Source # 

Methods

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

show1 :: f a -> String Source #

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

class Show2 f where Source #

Methods

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

showsPrec2 :: Show (f a b) => Int -> f a b -> ShowS Source #

show2 :: f a b -> String Source #

Instances

Show2 N N IFin Source # 

Methods

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

show2 :: f a b -> String Source #

Show2 [k] k (Remove k as) Source # 

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 #

Methods

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

showsPrec3 :: Show (f a b c) => Int -> f a b c -> ShowS Source #

show3 :: f a b c -> String Source #

Instances

Show3 [l] l [l] (Remove l) Source # 

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 #

Minimal complete definition

readsPrec1

Methods

readsPrec1 :: Int -> ReadS (Some f) Source #

Instances

Read1 Bool Boolean Source # 
Read1 N Nat Source # 

Methods

readsPrec1 :: Int -> ReadS (Some Nat f) Source #

Read1 N Fin Source # 

Methods

readsPrec1 :: Int -> ReadS (Some Fin f) Source #

Read r => Read1 k (C k r) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some (C k r) f) Source #

(Read1 k f, Read1 k g) => Read1 k ((:|:) k f g) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some ((k :|: f) g) f) Source #

Read1 [k] (Length k) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some (Length k) f) Source #

Read1 k f => Read1 [k] (Sum k f) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some (Sum k f) f) Source #

Read1 k f => Read1 [k] (Prod k f) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some (Prod k f) f) Source #

Read2 l k p => Read1 (k, l) (Uncur l k p) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some (Uncur l k p) f) Source #

(Read1 k f, Read1 l g) => Read1 (Either k l) ((:+:) l k f g) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some ((l :+: k) f g) f) Source #

Read3 m l k p => Read1 (k, l, m) (Uncur3 m l k p) Source # 

Methods

readsPrec1 :: Int -> ReadS (Some (Uncur3 m l k p) f) Source #

class Read2 f where Source #

Minimal complete definition

readsPrec2

Methods

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

Instances

Read2 N N IFin Source # 

Methods

readsPrec2 :: Int -> ReadS (Some2 IFin k f) Source #

Read2 l [l] (Index l) Source # 

Methods

readsPrec2 :: Int -> ReadS (Some2 (Index l) k f) Source #

class Read3 f where Source #

Minimal complete definition

readsPrec3

Methods

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

Instances

Read3 [l] l [l] (Remove l) Source # 

Methods

readsPrec3 :: Int -> ReadS (Some3 (Remove l) l k f) Source #

class Functor1 t where Source #

Minimal complete definition

map1

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 l l ((:&:) l f) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 l l ((:|:) l f) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 l l (VecT l n) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

(Functor1 m l f, Functor1 l k g) => Functor1 m k (Comp1 (k -> *) m (l -> *) f g) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 [k] k (Sum k) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 [k] k (Prod k) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 (Maybe k) 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).

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 [(k1, k)] k (Env k k1 k2) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 (Either k1 k) k ((:+:) k k1 f) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

Functor1 (k1, k) k ((:*:) k k1 f) Source # 

Methods

map1 :: (forall a. f a -> g a) -> t f b -> t g b Source #

class IxFunctor1 i t | t -> i where Source #

Minimal complete definition

imap1

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 # 

Methods

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

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

Methods

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

IxFunctor1 k [(m, k)] (IxList k (m, k) (IxSecond m k k ((:~:) k))) (Env k m k1) Source # 

Methods

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

IxFunctor1 k (m, k) (IxSecond m k k ((:~:) k)) ((:*:) k m f) Source # 

Methods

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

class Foldable1 t where Source #

Minimal complete definition

foldMap1

Methods

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

Instances

Foldable1 l l ((:&:) l f) Source # 

Methods

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

Foldable1 l l ((:|:) l f) Source # 

Methods

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

Foldable1 l l (VecT l n) Source # 

Methods

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

Foldable1 [k] k (Sum k) Source # 

Methods

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

Foldable1 [k] k (Prod k) Source # 

Methods

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

Foldable1 (Maybe k) k (Option k) Source # 

Methods

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

Foldable1 (Either k1 k) k ((:+:) k k1 f) Source # 

Methods

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

Foldable1 (k1, k) k ((:*:) k k1 f) Source # 

Methods

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

class IxFoldable1 i t | t -> i where Source #

Minimal complete definition

ifoldMap1

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 # 

Methods

ifoldMap1 :: Monoid m => (forall a. i b a -> f a -> m) -> t f b -> m Source #

IxFoldable1 k [k] (Index k) (Prod k) Source # 

Methods

ifoldMap1 :: Monoid m => (forall a. i b a -> f a -> m) -> t f b -> m Source #

class (Functor1 t, Foldable1 t) => Traversable1 t where Source #

Minimal complete definition

traverse1

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Instances

Traversable1 l l ((:&:) l f) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Traversable1 l l ((:|:) l f) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Traversable1 l l (VecT l n) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Traversable1 [k] k (Sum k) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Traversable1 [k] k (Prod k) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Traversable1 (Maybe k) k (Option k) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Traversable1 (Either k1 k) k ((:+:) k k1 f) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

Traversable1 (k1, k) k ((:*:) k k1 f) Source # 

Methods

traverse1 :: Applicative h => (forall a. f a -> h (g a)) -> t f b -> h (t g b) Source #

class (IxFunctor1 i t, IxFoldable1 i t) => IxTraversable1 i t | t -> i where Source #

Minimal complete definition

itraverse1

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 # 

Methods

itraverse1 :: Applicative h => (forall a. i b a -> f a -> h (g a)) -> t f b -> h (t g b) Source #

IxTraversable1 k [k] (Index k) (Prod k) Source # 

Methods

itraverse1 :: Applicative h => (forall a. i b a -> f a -> h (g a)) -> t f b -> h (t g b) Source #

class Bifunctor1 t where Source #

Minimal complete definition

bimap1

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 m m m ((:&:) m) Source # 

Methods

bimap1 :: (forall a. f a -> h a) -> (forall a. g a -> i a) -> t f g b -> t h i b Source #

Bifunctor1 m m m ((:|:) m) Source # 

Methods

bimap1 :: (forall a. f a -> h a) -> (forall a. g a -> i a) -> t f g b -> t h i b Source #

Bifunctor1 (Either k l) l k ((:+:) l k) Source # 

Methods

bimap1 :: (forall a. f a -> h a) -> (forall a. g a -> i a) -> t f g b -> t h i b Source #

Bifunctor1 (k, l) l k ((:*:) l k) Source # 

Methods

bimap1 :: (forall a. f a -> h a) -> (forall a. g a -> i a) -> t f g b -> t h i b Source #

class IxBifunctor1 i j t | t -> i j where Source #

Minimal complete definition

ibimap1

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 #

data Some f :: * where Source #

Constructors

Some :: f a -> Some f 

Instances

(TestEquality k f, Eq1 k f) => Eq (Some k f) Source # 

Methods

(==) :: Some k f -> Some k f -> Bool #

(/=) :: Some k f -> Some k f -> Bool #

some :: Some f -> (forall a. f a -> r) -> r Source #

An eliminator for a Some type.

Consider this function akin to a Monadic bind, except instead of binding into a Monad with a sequent function, we're binding into the existential quantification with a universal eliminator function.

It serves as an explicit delimiter in a program of where the type index may be used and depended on, and where it may not.

NB: the result type of the eliminating function may not refer to the universally quantified type index a.

(>>-) :: Some f -> (forall a. f a -> r) -> r infixl 1 Source #

(>->) :: (forall x. f x -> Some g) -> (forall x. g x -> Some h) -> f a -> Some h infixr 1 Source #

withSome :: (forall a. f a -> r) -> Some f -> r Source #

onSome :: (forall a. f a -> g x) -> Some f -> Some g Source #

msome :: Monad m => f a -> m (Some f) Source #

(>>=-) :: Monad m => m (Some f) -> (forall a. f a -> m r) -> m r infixl 1 Source #

data Some2 f :: * where Source #

Constructors

Some2 :: f a b -> Some2 f 

some2 :: Some2 f -> (forall a b. f a b -> r) -> r Source #

(>>--) :: Some2 f -> (forall a b. f a b -> r) -> r infixl 1 Source #

(>-->) :: (forall x y. f x y -> Some2 g) -> (forall x y. g x y -> Some2 h) -> f a b -> Some2 h infixr 1 Source #

withSome2 :: (forall a b. f a b -> r) -> Some2 f -> r Source #

onSome2 :: (forall a b. f a b -> g x y) -> Some2 f -> Some2 g Source #

msome2 :: Monad m => f a b -> m (Some2 f) Source #

(>>=--) :: Monad m => m (Some2 f) -> (forall a b. f a b -> m r) -> m r infixl 1 Source #

data Some3 f :: * where Source #

Constructors

Some3 :: f a b c -> Some3 f 

some3 :: Some3 f -> (forall a b c. f a b c -> r) -> r Source #

(>>---) :: Some3 f -> (forall a b c. f a b c -> r) -> r infixl 1 Source #

(>--->) :: (forall x y z. f x y z -> Some3 g) -> (forall x y z. g x y z -> Some3 h) -> f a b c -> Some3 h infixr 1 Source #

withSome3 :: (forall a b c. f a b c -> r) -> Some3 f -> r Source #

onSome3 :: (forall a b c. f a b c -> g x y z) -> Some3 f -> Some3 g Source #

msome3 :: Monad m => f a b c -> m (Some3 f) Source #

(>>=---) :: Monad m => m (Some3 f) -> (forall a b c. f a b c -> m r) -> m r infixl 1 Source #

data SomeC c f where Source #

Constructors

SomeC :: c a => f a -> SomeC c f 

someC :: SomeC c f -> (forall a. c a => f a -> r) -> r Source #

(>>~) :: SomeC c f -> (forall a. c a => f a -> r) -> r infixl 1 Source #

msomeC :: (Monad m, c a) => f a -> m (SomeC c f) Source #

(>>=~) :: Monad m => m (SomeC c f) -> (forall a. c a => f a -> m r) -> m r infixl 1 Source #