constrained-categories-0.3.1.1: 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 # 
Instance details

Defined in Control.Functor.Constrained

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 # 
Instance details

Defined in Control.Functor.Constrained

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 # 
Instance details

Defined in Control.Functor.Constrained

Functor Maybe (Discrete :: * -> * -> *) (Discrete :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Functor IO (Coercion :: * -> * -> *) (Coercion :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

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 # 
Instance details

Defined in Control.Functor.Constrained

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 # 
Instance details

Defined in Control.Functor.Constrained

Functor Complex (Discrete :: * -> * -> *) (Discrete :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

(Functor [] k k, o [UnitObject k]) => Functor [] (ConstrainedCategory k o) (ConstrainedCategory k o) Source # 
Instance details

Defined in Control.Functor.Constrained

Functor f => Functor f ((->) :: * -> * -> *) ((->) :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

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

Functor (Either a) (Discrete :: * -> * -> *) (Discrete :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

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

Functor (Either a) (Coercion :: * -> * -> *) (Coercion :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

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

Functor ((,) a) (Discrete :: * -> * -> *) (Discrete :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

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

Functor ((,) a) (Coercion :: * -> * -> *) (Coercion :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

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

Functor ((->) a :: * -> *) (Discrete :: * -> * -> *) (Discrete :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

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

Functor ((->) a :: * -> *) (Coercion :: * -> * -> *) (Coercion :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

fmap :: (Object Coercion a0, Object Coercion (a -> a0), Object Coercion b, Object Coercion (a -> b)) => Coercion a0 b -> Coercion (a -> a0) (a -> b) 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 [] ((->) :: * -> * -> *) ((->) :: * -> * -> *) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

sum2product :: (ObjectSum (->) a b, ObjectPair (->) [a] [b]) => [a + b] -> ([a], [b]) Source #

mapEither :: (Object (->) a, ObjectSum (->) b c, Object (->) [a], ObjectPair (->) [b] [c]) => (a -> b + c) -> [a] -> ([b], [c]) Source #

filter :: (Object (->) a, Object (->) Bool, Object (->) [a]) => (a -> Bool) -> [a] -> [a] Source #

(o (), o [()], o Void, o [Void]) => SumToProduct [] (ConstrainedCategory ((->) :: * -> * -> *) o) (ConstrainedCategory ((->) :: * -> * -> *) o) Source # 
Instance details

Defined in Control.Functor.Constrained

Methods

sum2product :: (ObjectSum (ConstrainedCategory (->) o) a b, ObjectPair (ConstrainedCategory (->) o) [a] [b]) => ConstrainedCategory (->) o [a + b] ([a], [b]) Source #

mapEither :: (Object (ConstrainedCategory (->) o) a, ObjectSum (ConstrainedCategory (->) o) b c, Object (ConstrainedCategory (->) o) [a], ObjectPair (ConstrainedCategory (->) o) [b] [c]) => ConstrainedCategory (->) o a (b + c) -> ConstrainedCategory (->) o [a] ([b], [c]) Source #

filter :: (Object (ConstrainedCategory (->) o) a, Object (ConstrainedCategory (->) o) Bool, Object (ConstrainedCategory (->) o) [a]) => ConstrainedCategory (->) o a Bool -> ConstrainedCategory (->) o [a] [a] Source #