constrained-categories-0.3.0.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

Data.Traversable.Constrained

Description

 

Synopsis

Documentation

class (Category k, Category l, Functor s l l, Functor t k k) => Traversable s t k l | s k l -> t, t k l -> s, s t k -> l, s t l -> k where Source

Minimal complete definition

traverse

Associated Types

type TraversalObject k t b :: Constraint Source

Methods

traverse :: (Monoidal f k l, Object l a, Object l (s a), ObjectPair k b (t b), ObjectPair l (f b) (f (t b)), TraversalObject k t b) => (a `l` f b) -> s a `l` f (t b) Source

mapM :: (k ~ l, s ~ t, Applicative m k k, Object k a, Object k (t a), ObjectPair k b (t b), ObjectPair k (m b) (m (t b)), TraversalObject k t b) => (a `k` m b) -> t a `k` m (t b) Source

traverse, restricted to endofunctors. May be more efficient to implement.

sequence :: (k ~ l, s ~ t, Monoidal f k k, ObjectPair k a (t a), ObjectPair k (f a) (f (t a)), Object k (t (f a)), TraversalObject k t a) => t (f a) `k` f (t a) Source

Instances

(Arrow k (->), WellPointed k, Function k, Functor [] k k) => Traversable [] [] k k Source 
(Arrow k (->), WellPointed k, Function k, Functor Maybe k k) => Traversable Maybe Maybe k k Source 

forM :: forall s t k m a b l. (Traversable s t k l, Monoidal m k l, Function l, Object k b, Object k (t b), ObjectPair k b (t b), Object l a, Object l (s a), ObjectPair l (m b) (m (t b)), TraversalObject k t b) => s a -> (a `l` m b) -> m (t b) Source

Flipped version of traverse / mapM.

type EndoTraversable t k = Traversable t t k k Source

A traversable that can be used with mapM.

haskTraverse :: (Traversable t, Monoidal f (->) (->)) => (a -> f b) -> t a -> f (t b) Source

Use this if you want to “derive” a constrained traversable instance from a given Traversable one. (You will not be able to simply set traverse = traverse, because the latter requires the Prelude version of Applicative, which can not be inferred from the constrained Monoidal.