Copyright | (c) Sergey Vinokurov 2019 |
---|---|
License | BSD-2 (see LICENSE) |
Maintainer | sergey@debian |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class (CFunctor f, CFoldable f) => CTraversable f where
- ctraverse :: (Constraints f a, Constraints f b, Monad m) => (a -> m b) -> f a -> m (f b)
- csequence :: (Constraints f a, Constraints f (m a), Monad m) => f (m a) -> m (f a)
- cfor :: (CTraversable f, Constraints f a, Constraints f b, Monad m) => f a -> (a -> m b) -> m (f b)
- class Constrained (f :: k2 -> k1) where
- type Constraints (f :: k2 -> k1) :: k2 -> Constraint
Documentation
class (CFunctor f, CFoldable f) => CTraversable f where Source #
Like Traversable
but allows elements to have constraints on them.
Laws are the same:
ctraverse pure == pure ctraverse (f <=< g) == ctraverse f <=< ctraverse g
NB There's no aplicative version because Vectors from the
http://hackage.haskell.org/package/vector package only support
monadic traversals. Since they're one of the main motivation for
this package, Applicative
version of traversals will not exist.
Nothing
ctraverse :: (Constraints f a, Constraints f b, Monad m) => (a -> m b) -> f a -> m (f b) Source #
csequence :: (Constraints f a, Constraints f (m a), Monad m) => f (m a) -> m (f a) Source #
ctraverse :: (Constraints f a, Constraints f b, Monad m, Traversable f) => (a -> m b) -> f a -> m (f b) Source #
Instances
cfor :: (CTraversable f, Constraints f a, Constraints f b, Monad m) => f a -> (a -> m b) -> m (f b) Source #
ctraverse
with araguments flipped.
class Constrained (f :: k2 -> k1) Source #
Specification of constrains that a functor might impose on its elements. For example, sets typically require that their elements are ordered and unboxed vectors require elements to have an instance of special class that allows them to be packed in memory.
NB The Constraints
type family is associated with a typeclass in
order to improve type inference. Whenever a typeclass constraint
will be present, instance is guaranteed to exist and typechecker is
going to take advantage of that.
type Constraints (f :: k2 -> k1) :: k2 -> Constraint Source #