Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Import this module qualified, like this:
import qualified Rank2
This will bring into scope the standard classes Functor
, Applicative
, Foldable
, and Traversable
, but with a
Rank2.
prefix and a twist that their methods operate on a heterogenous collection. The same property is shared by
the two less standard classes Apply
and Distributive
.
- class Functor g where
- class Functor g => Apply g where
- class Apply g => Applicative g where
- class Foldable g where
- class (Functor g, Foldable g) => Traversable g where
- class DistributiveTraversable g => Distributive g where
- class Functor g => DistributiveTraversable (g :: (k -> *) -> *) where
- distributeJoin :: (Distributive g, Monad f) => f (g f) -> g f
- newtype Compose k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1) :: forall k k1. (k -> *) -> (k1 -> k) -> k1 -> * = Compose {
- getCompose :: f (g a)
- data Empty f = Empty
- newtype Only a f = Only {
- fromOnly :: f a
- newtype Identity g f = Identity {
- runIdentity :: g f
- data Product g h f = Pair {}
- newtype Arrow p q a = Arrow {
- apply :: p a -> q a
- ap :: Apply g => g (Arrow p q) -> g p -> g q
- fmap :: Functor g => (forall a. p a -> q a) -> g p -> g q
- liftA4 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a) -> g p -> g q -> g r -> g s -> g t
- liftA5 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a -> u a) -> g p -> g q -> g r -> g s -> g t -> g u
- fmapTraverse :: (DistributiveTraversable f, Traversable g) => (forall a. g (t a) -> u a) -> g (f t) -> f u
- liftA2Traverse1 :: (Apply f, DistributiveTraversable f, Traversable g) => (forall a. g (t a) -> u a -> v a) -> g (f t) -> f u -> f v
- liftA2Traverse2 :: (Apply f, DistributiveTraversable f, Traversable g) => (forall a. t a -> g (u a) -> v a) -> f t -> g (f u) -> f v
- liftA2TraverseBoth :: (Apply f, DistributiveTraversable f, Traversable g1, Traversable g2) => (forall a. g1 (t a) -> g2 (u a) -> v a) -> g1 (f t) -> g2 (f u) -> f v
- distributeWith :: (Distributive g, Functor f) => (forall i. f (a i) -> b i) -> f (g a) -> g b
- distributeWithTraversable :: (DistributiveTraversable g, Traversable m) => (forall a. m (p a) -> q a) -> m (g p) -> g q
Rank 2 classes
class Functor g where Source #
Equivalent of Functor
for rank 2 data types, satisfying the usual functor laws
id <$> g == g (p . q) <$> g == p <$> (q <$> g)
class Functor g => Apply g where Source #
Subclass of Functor
halfway to Applicative
, satisfying
(.) <$> u <*> v <*> w == u <*> (v <*> w)
(<*>) :: g (Arrow p q) -> g p -> g q Source #
Equivalent of <*>
for rank 2 data types
liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #
Equivalent of liftA2
for rank 2 data types
liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #
Equivalent of liftA3
for rank 2 data types
class Apply g => Applicative g where Source #
Equivalent of Applicative
for rank 2 data types
Applicative k (Empty (k -> *)) Source # | |
Applicative k (Only k x) Source # | |
Applicative k g => Applicative k (Identity (k -> *) g) Source # | |
(Applicative k g, Applicative k h) => Applicative k (Product (k -> *) g h) Source # | |
class (Functor g, Foldable g) => Traversable g where Source #
Equivalent of Traversable
for rank 2 data types
traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #
sequence :: Applicative m => g (Compose m p) -> m (g p) Source #
Traversable k (Empty (k -> *)) Source # | |
Traversable k (Only k x) Source # | |
Traversable k g => Traversable k (Identity (k -> *) g) Source # | |
(Traversable k g, Traversable k h) => Traversable k (Product (k -> *) g h) Source # | |
class DistributiveTraversable g => Distributive g where Source #
Equivalent of Distributive
for rank 2 data types
collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose f1 f2) Source #
distribute :: Functor f1 => f1 (g f2) -> g (Compose f1 f2) Source #
cotraverse :: Functor m => (forall a. m (p a) -> q a) -> m (g p) -> g q Source #
Dual of traverse
, equivalent of cotraverse
for rank 2 data types
Distributive k (Empty (k -> *)) Source # | |
Distributive k (Only k x) Source # | |
Distributive k g => Distributive k (Identity (k -> *) g) Source # | |
(Distributive k g, Distributive k h) => Distributive k (Product (k -> *) g h) Source # | |
class Functor g => DistributiveTraversable (g :: (k -> *) -> *) where Source #
A weaker Distributive
that requires Traversable
to use, not just a Functor
.
collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose f1 f2) Source #
distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose f1 f2) Source #
cotraverseTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #
cotraverseTraversable :: (Traversable m, Distributive g) => (forall a. m (p a) -> q a) -> m (g p) -> g q Source #
DistributiveTraversable k (Empty (k -> *)) Source # | |
DistributiveTraversable k (Only k x) Source # | |
DistributiveTraversable k g => DistributiveTraversable k (Identity (k -> *) g) Source # | |
(DistributiveTraversable k g, DistributiveTraversable k h) => DistributiveTraversable k (Product (k -> *) g h) Source # | |
distributeJoin :: (Distributive g, Monad f) => f (g f) -> g f Source #
A variant of distribute
convenient with Monad
instances
Rank 2 data types
newtype Compose k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1) :: forall k k1. (k -> *) -> (k1 -> k) -> k1 -> * infixr 9 #
Right-to-left composition of functors. The composition of applicative functors is always applicative, but the composition of monads is not always a monad.
Compose infixr 9 | |
|
Functor f => Generic1 k (Compose * k f g) | |
(Functor f, Functor g) => Functor (Compose * * f g) | Since: 4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Compose * * f g) | Since: 4.9.0.0 |
(Foldable f, Foldable g) => Foldable (Compose * * f g) | Since: 4.9.0.0 |
(Traversable f, Traversable g) => Traversable (Compose * * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Compose * * f g) | Since: 4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Compose * * f g) | Since: 4.9.0.0 |
(Read1 f, Read1 g) => Read1 (Compose * * f g) | Since: 4.9.0.0 |
(Show1 f, Show1 g) => Show1 (Compose * * f g) | Since: 4.9.0.0 |
(Alternative f, Applicative g) => Alternative (Compose * * f g) | Since: 4.9.0.0 |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose * * f g a) | Since: 4.9.0.0 |
(Data (f (g a)), Typeable * k2, Typeable * k1, Typeable (k2 -> k1) g, Typeable (k1 -> *) f, Typeable k2 a) => Data (Compose k1 k2 f g a) | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) | Since: 4.9.0.0 |
(Read1 f, Read1 g, Read a) => Read (Compose * * f g a) | Since: 4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Compose * * f g a) | Since: 4.9.0.0 |
Generic (Compose k1 k2 f g a) | |
type Rep1 k (Compose * k f g) | |
type Rep (Compose k1 k2 f g a) | |
A rank-2 equivalent of '()', a zero-element tuple
DistributiveTraversable k (Empty (k -> *)) Source # | |
Distributive k (Empty (k -> *)) Source # | |
Applicative k (Empty (k -> *)) Source # | |
Apply k (Empty (k -> *)) Source # | |
Traversable k (Empty (k -> *)) Source # | |
Foldable k (Empty (k -> *)) Source # | |
Functor k (Empty (k -> *)) Source # | |
Eq (Empty k f) Source # | |
Ord (Empty k f) Source # | |
Show (Empty k f) Source # | |
A rank-2 tuple of only one element
DistributiveTraversable k (Only k x) Source # | |
Distributive k (Only k x) Source # | |
Applicative k (Only k x) Source # | |
Apply k (Only k x) Source # | |
Traversable k (Only k x) Source # | |
Foldable k (Only k x) Source # | |
Functor k (Only k a) Source # | |
Eq (f a) => Eq (Only k a f) Source # | |
Ord (f a) => Ord (Only k a f) Source # | |
Show (f a) => Show (Only k a f) Source # | |
Equivalent of Identity
for rank 2 data types
Identity | |
|
DistributiveTraversable k g => DistributiveTraversable k (Identity (k -> *) g) Source # | |
Distributive k g => Distributive k (Identity (k -> *) g) Source # | |
Applicative k g => Applicative k (Identity (k -> *) g) Source # | |
Apply k g => Apply k (Identity (k -> *) g) Source # | |
Traversable k g => Traversable k (Identity (k -> *) g) Source # | |
Foldable k g => Foldable k (Identity (k -> *) g) Source # | |
Functor k g => Functor k (Identity (k -> *) g) Source # | |
Eq (g f) => Eq (Identity k g f) Source # | |
Ord (g f) => Ord (Identity k g f) Source # | |
Show (g f) => Show (Identity k g f) Source # | |
Equivalent of Product
for rank 2 data types
(DistributiveTraversable k g, DistributiveTraversable k h) => DistributiveTraversable k (Product (k -> *) g h) Source # | |
(Distributive k g, Distributive k h) => Distributive k (Product (k -> *) g h) Source # | |
(Applicative k g, Applicative k h) => Applicative k (Product (k -> *) g h) Source # | |
(Apply k g, Apply k h) => Apply k (Product (k -> *) g h) Source # | |
(Traversable k g, Traversable k h) => Traversable k (Product (k -> *) g h) Source # | |
(Foldable k g, Foldable k h) => Foldable k (Product (k -> *) g h) Source # | |
(Functor k g, Functor k h) => Functor k (Product (k -> *) g h) Source # | |
(Eq (h f), Eq (g f)) => Eq (Product k g h f) Source # | |
(Ord (h f), Ord (g f)) => Ord (Product k g h f) Source # | |
(Show (h f), Show (g f)) => Show (Product k g h f) Source # | |
Wrapper for functions that map the argument constructor type
Method synonyms and helper functions
liftA4 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a) -> g p -> g q -> g r -> g s -> g t Source #
liftA5 :: Apply g => (forall a. p a -> q a -> r a -> s a -> t a -> u a) -> g p -> g q -> g r -> g s -> g t -> g u Source #
fmapTraverse :: (DistributiveTraversable f, Traversable g) => (forall a. g (t a) -> u a) -> g (f t) -> f u Source #
Like fmap
, but traverses over its argument
liftA2Traverse1 :: (Apply f, DistributiveTraversable f, Traversable g) => (forall a. g (t a) -> u a -> v a) -> g (f t) -> f u -> f v Source #
Like liftA2
, but traverses over its first argument
liftA2Traverse2 :: (Apply f, DistributiveTraversable f, Traversable g) => (forall a. t a -> g (u a) -> v a) -> f t -> g (f u) -> f v Source #
Like liftA2
, but traverses over its second argument
liftA2TraverseBoth :: (Apply f, DistributiveTraversable f, Traversable g1, Traversable g2) => (forall a. g1 (t a) -> g2 (u a) -> v a) -> g1 (f t) -> g2 (f u) -> f v Source #
Like liftA2
, but traverses over both its arguments
distributeWith :: (Distributive g, Functor f) => (forall i. f (a i) -> b i) -> f (g a) -> g b Source #
Deprecated: Use cotraverse instead.
Synonym for cotraverse
distributeWithTraversable :: (DistributiveTraversable g, Traversable m) => (forall a. m (p a) -> q a) -> m (g p) -> g q Source #
Deprecated: Use cotraverseTraversable instead.
Synonym for cotraverseTraversable