generalised-functor-0.0.4: Generalisng Functors

Safe HaskellNone
LanguageHaskell2010

Control.GeneralisedFunctor.Functor

Description

 

Documentation

type family FunctorParam c t' Source

Instances

type FunctorParam (->) [_1] = OrdinaryFunctorParam [] Source 
type FunctorParam (->) (IO _1) = OrdinaryFunctorParam IO Source 
type FunctorParam (->) (ArgOrder _1) = OrdinaryFunctorParam ArgOrder Source 
type FunctorParam (->) (OptDescr _1) = OrdinaryFunctorParam OptDescr Source 
type FunctorParam (->) (ArgDescr _1) = OrdinaryFunctorParam ArgDescr Source 
type FunctorParam (->) (Identity _1) = OrdinaryFunctorParam Identity Source 
type FunctorParam (->) (ZipList _1) = OrdinaryFunctorParam ZipList Source 
type FunctorParam (->) (Handler _1) = OrdinaryFunctorParam Handler Source 
type FunctorParam (->) (STM _1) = OrdinaryFunctorParam STM Source 
type FunctorParam (->) (First _1) = OrdinaryFunctorParam First Source 
type FunctorParam (->) (Last _1) = OrdinaryFunctorParam Last Source 
type FunctorParam (->) (ReadPrec _1) = OrdinaryFunctorParam ReadPrec Source 
type FunctorParam (->) (ReadP _1) = OrdinaryFunctorParam ReadP Source 
type FunctorParam (->) (Maybe _1) = OrdinaryFunctorParam Maybe Source 
type FunctorParam (->) (r -> _1) = OrdinaryFunctorParam ((->) r) Source 
type FunctorParam (->) (Either a _1) = OrdinaryFunctorParam (Either a) Source 
type FunctorParam (->) (_1, _1) Source 
type FunctorParam (->) (ST s _1) = OrdinaryFunctorParam (ST s) Source 
type FunctorParam (->) (Const m _1) = OrdinaryFunctorParam (Const m) Source 
type FunctorParam (->) (WrappedMonad m _1) = OrdinaryFunctorParam (WrappedMonad m) Source 
type FunctorParam (->) (ArrowMonad a _1) = OrdinaryFunctorParam (ArrowMonad a) Source 
type FunctorParam (->) (Proxy * _1) = OrdinaryFunctorParam (Proxy *) Source 
type FunctorParam (->) (ST s _1) = OrdinaryFunctorParam (ST s) Source 
type FunctorParam (->) (WrappedArrow a b _1) = OrdinaryFunctorParam (WrappedArrow a b) Source 
type FunctorParam (->) (Alt * f _1) = OrdinaryFunctorParam (Alt * f) Source 

class Functor f where Source

Associated Types

type FunctorInput f t Source

type FunctorOutput f t Source

type FunctorCategory f :: * -> * -> * Source

Methods

fmap :: (Category c, f ~ FunctorParam c a', f ~ FunctorParam c b', a ~ FunctorInput f a', b ~ FunctorInput f b', a' ~ FunctorOutput f a, b' ~ FunctorOutput f b, c ~ FunctorCategory f) => c a b -> c a' b' Source

class ExoFunctor c c' where Source

Associated Types

type ExoInput c c' t' Source

type ExoOutput c c' t' Source

Methods

exomap :: (Category c, Category c', a ~ ExoInput c c' a', b ~ ExoInput c c' b', a' ~ ExoOutput c c' a, b' ~ ExoOutput c c' b) => c a b -> c' a' b' Source

Instances

type family ContraFunctorParam c t' Source

Instances

type ContraFunctorParam (->) (_1 -> r) Source 

class ContraFunctor f where Source

Associated Types

type ContraFunctorInput f t' Source

type ContraFunctorOutput f t' Source

type ContraFunctorCategory f :: * -> * -> * Source

Methods

contramap :: (Category c, f ~ ContraFunctorParam c a', f ~ ContraFunctorParam c b', a ~ ContraFunctorInput f a', b ~ ContraFunctorInput f b', a' ~ ContraFunctorOutput f a, b' ~ ContraFunctorOutput f b, c ~ ContraFunctorCategory f) => c a b -> c b' a' Source

class ExoContraFunctor c c' where Source

Associated Types

type ExoContraInput c c' t' Source

type ExoContraOutput c c' t' Source

Methods

exocontramap :: (Category c, Category c', a ~ ExoContraInput c c' a', b ~ ExoContraInput c c' b', a' ~ ExoContraOutput c c' a, b' ~ ExoContraOutput c c' b) => c a b -> c' b' a' Source