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

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

Type.Class.HFunctor

Description

Higher order functors, foldables, and traversables, along with their indexed variants. (oh, and bifunctors tacked on for good measure.)

Documentation

class HFunctor t where Source

Methods

map' :: (forall a. f a -> g a) -> t f b -> t g b Source

Take a natural transformation to a lifted natural transformation.

Instances

HFunctor k k (IT k) Source 
HFunctor k k ((:&:) k f) Source 
HFunctor k k ((:+:) k f) Source 
HFunctor k k (CT k k r) Source 
HFunctor k k (RR k k g) Source 
HFunctor 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).

HFunctor k [k] (Sum k) Source 
HFunctor k [k] (Prod k) Source 
HFunctor k ((,) k k) ((:*:) k k f) Source 
HFunctor k (Either k k) ((:|:) k k f) Source 
HFunctor k (k -> k) (LL k k a) Source 

class HIxFunctor i t | t -> i where Source

Methods

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

Instances

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

class HFoldable t where Source

Methods

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

Instances

HFoldable k k (IT k) Source 
HFoldable k k ((:&:) k f) Source 
HFoldable k k ((:+:) k f) Source 
HFoldable k k (CT k k r) Source 
HFoldable k k (RR k k g) Source 
HFoldable k (Maybe k) (Option k) Source 
HFoldable k [k] (Sum k) Source 
HFoldable k [k] (Prod k) Source 
HFoldable k ((,) k k) ((:*:) k k f) Source 
HFoldable k (Either k k) ((:|:) k k f) Source 
HFoldable k (k -> k) (LL k k a) Source 

class HIxFoldable i t | t -> i where Source

Methods

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

Instances

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

class (HFunctor t, HFoldable t) => HTraversable t where Source

Methods

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

Instances

HTraversable k k (IT k) Source 
HTraversable k k ((:&:) k f) Source 
HTraversable k k ((:+:) k f) Source 
HTraversable k k (CT k k r) Source 
HTraversable k k (RR k k g) Source 
HTraversable k (Maybe k) (Option k) Source 
HTraversable k [k] (Sum k) Source 
HTraversable k [k] (Prod k) Source 
HTraversable k ((,) k k) ((:*:) k k f) Source 
HTraversable k (Either k k) ((:|:) k k f) Source 
HTraversable k (k -> k) (LL k k a) Source 

class (HIxFunctor i t, HIxFoldable i t) => HIxTraversable i t | t -> i where Source

Methods

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

Instances

HIxTraversable [k] k (Index k) (Sum k) Source 

class HBifunctor t where Source

Methods

bimap' :: (forall a. f a -> h a) -> (forall a. g a -> i a) -> t f g b -> t h i b Source

Instances

HBifunctor k k k ((:&:) k) Source 
HBifunctor k k k ((:+:) k) Source 
HBifunctor k k ((,) k k) ((:*:) k k) Source 
HBifunctor k k (Either k k) ((:|:) k k) Source