constrained-categories-0.3.1.0: Constrained clones of the category-theory type classes, using ConstraintKinds.

Copyright(c) 2014 Justus Sagemüller
LicenseGPL v3 (see COPYING)
Maintainer(@) sagemueller $ geo.uni-koeln.de
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Functor.Constrained

Contents

Description

 

Synopsis

Documentation

Functors

class (Category r, Category t, Object t (f (UnitObject r))) => Functor f r t | f r -> t, f t -> r where Source #

Minimal complete definition

fmap

Methods

fmap :: (Object r a, Object t (f a), Object r b, Object t (f b)) => r a b -> t (f a) (f b) Source #

Instances

Functor [] (Coercion *) (Coercion *) Source # 

Methods

fmap :: (Object (Coercion *) a, Object (Coercion *) [a], Object (Coercion *) b, Object (Coercion *) [b]) => Coercion * a b -> Coercion * [a] [b] Source #

Functor [] (Discrete *) (Discrete *) Source # 

Methods

fmap :: (Object (Discrete *) a, Object (Discrete *) [a], Object (Discrete *) b, Object (Discrete *) [b]) => Discrete * a b -> Discrete * [a] [b] Source #

Functor Maybe (Coercion *) (Coercion *) Source # 

Methods

fmap :: (Object (Coercion *) a, Object (Coercion *) (Maybe a), Object (Coercion *) b, Object (Coercion *) (Maybe b)) => Coercion * a b -> Coercion * (Maybe a) (Maybe b) Source #

Functor Maybe (Discrete *) (Discrete *) Source # 

Methods

fmap :: (Object (Discrete *) a, Object (Discrete *) (Maybe a), Object (Discrete *) b, Object (Discrete *) (Maybe b)) => Discrete * a b -> Discrete * (Maybe a) (Maybe b) Source #

Functor IO (Coercion *) (Coercion *) Source # 

Methods

fmap :: (Object (Coercion *) a, Object (Coercion *) (IO a), Object (Coercion *) b, Object (Coercion *) (IO b)) => Coercion * a b -> Coercion * (IO a) (IO b) Source #

Functor IO (Discrete *) (Discrete *) Source # 

Methods

fmap :: (Object (Discrete *) a, Object (Discrete *) (IO a), Object (Discrete *) b, Object (Discrete *) (IO b)) => Discrete * a b -> Discrete * (IO a) (IO b) Source #

Functor Complex (Coercion *) (Coercion *) Source # 
Functor Complex (Discrete *) (Discrete *) Source # 
(Functor [] k k, o [UnitObject k]) => Functor [] (ConstrainedCategory k o) (ConstrainedCategory k o) Source # 
Functor f => Functor f ((->) LiftedRep LiftedRep) ((->) LiftedRep LiftedRep) Source # 

Methods

fmap :: (Object (LiftedRep -> LiftedRep) a, Object (LiftedRep -> LiftedRep) (f a), Object (LiftedRep -> LiftedRep) b, Object (LiftedRep -> LiftedRep) (f b)) => (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) (f a) (f b) Source #

Functor (Either a) (Discrete *) (Discrete *) Source # 

Methods

fmap :: (Object (Discrete *) a, Object (Discrete *) (Either a a), Object (Discrete *) b, Object (Discrete *) (Either a b)) => Discrete * a b -> Discrete * (Either a a) (Either a b) Source #

Functor (Either a) (Coercion *) (Coercion *) Source # 

Methods

fmap :: (Object (Coercion *) a, Object (Coercion *) (Either a a), Object (Coercion *) b, Object (Coercion *) (Either a b)) => Coercion * a b -> Coercion * (Either a a) (Either a b) Source #

Functor ((,) a) (Discrete *) (Discrete *) Source # 

Methods

fmap :: (Object (Discrete *) a, Object (Discrete *) (a, a), Object (Discrete *) b, Object (Discrete *) (a, b)) => Discrete * a b -> Discrete * (a, a) (a, b) Source #

Functor ((,) a) (Coercion *) (Coercion *) Source # 

Methods

fmap :: (Object (Coercion *) a, Object (Coercion *) (a, a), Object (Coercion *) b, Object (Coercion *) (a, b)) => Coercion * a b -> Coercion * (a, a) (a, b) Source #

Functor ((->) LiftedRep LiftedRep a) (Discrete *) (Discrete *) Source # 
Functor ((->) LiftedRep LiftedRep a) (Coercion *) (Coercion *) Source # 

(<$>) :: (Functor f r (->), Object r a, Object r b) => r a b -> f a -> f b infixl 4 Source #

constrainedFmap :: (Category r, Category t, o a, o b, o (f a), o (f b)) => (r a b -> t (f a) (f b)) -> ConstrainedCategory r o a b -> ConstrainedCategory t o (f a) (f b) Source #

[Co]product mapping

class (CoCartesian r, Cartesian t, Functor f r t, Object t (f (ZeroObject r))) => SumToProduct f r t where Source #

It is fairly common for functors (typically, container-like) to map Either to tuples in a natural way, thus "separating the variants". This is related to Foldable (with list and tuple monoids), but rather more effective.

Minimal complete definition

sum2product, mapEither, filter

Methods

sum2product :: (ObjectSum r a b, ObjectPair t (f a) (f b)) => t (f (a + b)) (f a, f b) Source #

  sum2product ≡ mapEither id
  

mapEither :: (Object r a, ObjectSum r b c, Object t (f a), ObjectPair t (f b) (f c)) => r a (b + c) -> t (f a) (f b, f c) Source #

  mapEither f ≡ sum2product . fmap f
  

filter :: (Object r a, Object r Bool, Object t (f a)) => r a Bool -> t (f a) (f a) Source #

Instances

SumToProduct [] ((->) LiftedRep LiftedRep) ((->) LiftedRep LiftedRep) Source # 
(o (), o [()], o Void, o [Void]) => SumToProduct [] (ConstrainedCategory ((->) LiftedRep LiftedRep) o) (ConstrainedCategory ((->) LiftedRep LiftedRep) o) Source #