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 Functor g => Distributive g where
- newtype Compose k k1 f g a :: forall k k1. (k1 -> *) -> (k -> k1) -> k -> * = 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
- liftA3 :: Apply g => (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s
Rank 2 classes
class Functor g => Apply g where Source #
Subclass of Functor
halfway to Applicative
(.) <$> u <*> v <*> w == u <*> (v <*> w)
class Apply g => Applicative g where Source #
Equivalent of Applicative
for rank 2 data types
Applicative Empty Source # | |
Applicative g => Applicative (Identity g) Source # | |
Applicative (Only x) Source # | |
(Applicative g, Applicative h) => Applicative (Product 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 Empty Source # | |
Traversable g => Traversable (Identity g) Source # | |
Traversable (Only x) Source # | |
(Traversable g, Traversable h) => Traversable (Product g h) Source # | |
class Functor 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 #
distributeWith :: Functor f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #
distributeM :: Monad f => f (g f) -> g f Source #
Distributive Empty Source # | |
Distributive g => Distributive (Identity g) Source # | |
Distributive (Only x) Source # | |
(Distributive g, Distributive h) => Distributive (Product g h) Source # | |
Rank 2 data types
newtype Compose k k1 f g a :: forall k k1. (k1 -> *) -> (k -> k1) -> k -> * 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, Functor g) => Functor (Compose * * f g) | |
(Applicative f, Applicative g) => Applicative (Compose * * f g) | |
(Foldable f, Foldable g) => Foldable (Compose * * f g) | |
(Traversable f, Traversable g) => Traversable (Compose * * f g) | |
Functor f => Generic1 (Compose * * f g) | |
(Eq1 f, Eq1 g) => Eq1 (Compose * * f g) | |
(Ord1 f, Ord1 g) => Ord1 (Compose * * f g) | |
(Read1 f, Read1 g) => Read1 (Compose * * f g) | |
(Show1 f, Show1 g) => Show1 (Compose * * f g) | |
(Alternative f, Applicative g) => Alternative (Compose * * f g) | |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose * * f g a) | |
(Data (f (g a)), Typeable * k, Typeable * k1, Typeable (k1 -> k) g, Typeable (k -> *) f, Typeable k1 a) => Data (Compose k1 k f g a) | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) | |
(Read1 f, Read1 g, Read a) => Read (Compose * * f g a) | |
(Show1 f, Show1 g, Show a) => Show (Compose * * f g a) | |
Generic (Compose k1 k f g a) | |
type Rep1 (Compose * * f g) | |
type Rep (Compose k1 k f g a) | |
A rank-2 equivalent of '()', a zero-element tuple
A rank-2 tuple of only one element
Equivalent of Identity
for rank 2 data types
Identity | |
|
Distributive g => Distributive (Identity g) Source # | |
Applicative g => Applicative (Identity g) Source # | |
Apply g => Apply (Identity g) Source # | |
Traversable g => Traversable (Identity g) Source # | |
Foldable g => Foldable (Identity g) Source # | |
Functor g => Functor (Identity g) Source # | |
Eq (g f) => Eq (Identity g f) Source # | |
Ord (g f) => Ord (Identity g f) Source # | |
Show (g f) => Show (Identity g f) Source # | |
Equivalent of Product
for rank 2 data types
(Distributive g, Distributive h) => Distributive (Product g h) Source # | |
(Applicative g, Applicative h) => Applicative (Product g h) Source # | |
(Apply g, Apply h) => Apply (Product g h) Source # | |
(Traversable g, Traversable h) => Traversable (Product g h) Source # | |
(Foldable g, Foldable h) => Foldable (Product g h) Source # | |
(Functor g, Functor h) => Functor (Product g h) Source # | |
(Eq (h f), Eq (g f)) => Eq (Product g h f) Source # | |
(Ord (h f), Ord (g f)) => Ord (Product g h f) Source # | |
(Show (h f), Show (g f)) => Show (Product g h f) Source # | |
Wrapper for functions that map the argument constructor type