rank2classes-0.2: a mirror image of some standard type classes, with methods of rank 2 types

Safe HaskellSafe
LanguageHaskell2010

Rank2

Contents

Description

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.

Synopsis

Rank 2 classes

class Functor g where Source #

Equivalent of Functor for rank 2 data types

Minimal complete definition

(<$>)

Methods

(<$>) :: (forall a. p a -> q a) -> g p -> g q Source #

Instances

Functor k (Empty (k -> *)) Source # 

Methods

(<$>) :: (forall a. p a -> q a) -> g p -> g q Source #

Functor k g => Functor k (Identity (k -> *) g) Source # 

Methods

(<$>) :: (forall a. p a -> q a) -> g p -> g q Source #

Functor k (Only k a) Source # 

Methods

(<$>) :: (forall b. p b -> q b) -> g p -> g q Source #

(Functor k g, Functor k h) => Functor k (Product (k -> *) g h) Source # 

Methods

(<$>) :: (forall a. p a -> q a) -> g p -> g q Source #

class Functor g => Apply g where Source #

Subclass of Functor halfway to Applicative

(.) <$> u <*> v <*> w == u <*> (v <*> w)

Minimal complete definition

liftA2 | (<*>)

Methods

(<*>) :: 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

Instances

Apply k (Empty (k -> *)) Source # 

Methods

(<*>) :: g (Arrow (Empty (k -> *)) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

Apply k g => Apply k (Identity (k -> *) g) Source # 

Methods

(<*>) :: g (Arrow (Identity (k -> *) g) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

Apply k (Only k x) Source # 

Methods

(<*>) :: g (Arrow (Only k x) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

(Apply k g, Apply k h) => Apply k (Product (k -> *) g h) Source # 

Methods

(<*>) :: g (Arrow (Product (k -> *) g h) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

class Apply g => Applicative g where Source #

Equivalent of Applicative for rank 2 data types

Minimal complete definition

pure

Methods

pure :: (forall a. f a) -> g f Source #

Instances

Applicative k (Empty (k -> *)) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

Applicative k g => Applicative k (Identity (k -> *) g) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

Applicative k (Only k x) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

(Applicative k g, Applicative k h) => Applicative k (Product (k -> *) g h) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

class Foldable g where Source #

Equivalent of Foldable for rank 2 data types

Minimal complete definition

foldMap

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

Instances

Foldable k (Empty (k -> *)) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

Foldable k g => Foldable k (Identity (k -> *) g) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

Foldable k (Only k x) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

(Foldable k g, Foldable k h) => Foldable k (Product (k -> *) g h) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

class (Functor g, Foldable g) => Traversable g where Source #

Equivalent of Traversable for rank 2 data types

Minimal complete definition

traverse | sequence

Methods

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 #

Instances

Traversable k (Empty (k -> *)) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Empty (k -> *)) * m p) -> m (g p) Source #

Traversable k g => Traversable k (Identity (k -> *) g) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Identity (k -> *) g) * m p) -> m (g p) Source #

Traversable k (Only k x) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Only k x) * m p) -> m (g p) Source #

(Traversable k g, Traversable k h) => Traversable k (Product (k -> *) g h) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Product (k -> *) g h) * m p) -> m (g p) Source #

class DistributiveTraversable g => Distributive g where Source #

Equivalent of Distributive for rank 2 data types

Minimal complete definition

distributeWith

Methods

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 #

Instances

Distributive k (Empty (k -> *)) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distributeWith :: Functor f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

Distributive k g => Distributive k (Identity (k -> *) g) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distributeWith :: Functor f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

Distributive k (Only k x) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Only k x) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Only k x) * f1 f2) Source #

distributeWith :: Functor f1 => (forall a. f1 (f2 a) -> f a) -> f1 (g f2) -> g f Source #

(Distributive k g, Distributive k h) => Distributive k (Product (k -> *) g h) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distributeWith :: Functor f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

class Functor g => DistributiveTraversable g where Source #

A weaker Distributive that requires Traversable to use, not just a Functor.

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

distributeWithTraversable :: (Traversable f1, Distributive g) => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

Instances

DistributiveTraversable k (Empty (k -> *)) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

DistributiveTraversable k g => DistributiveTraversable k (Identity (k -> *) g) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

DistributiveTraversable k (Only k x) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Only k x) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Only k x) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall a. f1 (f2 a) -> f a) -> f1 (g f2) -> g f Source #

(DistributiveTraversable k g, DistributiveTraversable k h) => DistributiveTraversable k (Product (k -> *) g h) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f 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 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.

Constructors

Compose infixr 9 

Fields

Instances

(Functor f, Functor g) => Functor (Compose * * f g) 

Methods

fmap :: (a -> b) -> Compose * * f g a -> Compose * * f g b #

(<$) :: a -> Compose * * f g b -> Compose * * f g a #

(Applicative f, Applicative g) => Applicative (Compose * * f g) 

Methods

pure :: a -> Compose * * f g a #

(<*>) :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b #

(*>) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g b #

(<*) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g a #

(Foldable f, Foldable g) => Foldable (Compose * * f g) 

Methods

fold :: Monoid m => Compose * * f g m -> m #

foldMap :: Monoid m => (a -> m) -> Compose * * f g a -> m #

foldr :: (a -> b -> b) -> b -> Compose * * f g a -> b #

foldr' :: (a -> b -> b) -> b -> Compose * * f g a -> b #

foldl :: (b -> a -> b) -> b -> Compose * * f g a -> b #

foldl' :: (b -> a -> b) -> b -> Compose * * f g a -> b #

foldr1 :: (a -> a -> a) -> Compose * * f g a -> a #

foldl1 :: (a -> a -> a) -> Compose * * f g a -> a #

toList :: Compose * * f g a -> [a] #

null :: Compose * * f g a -> Bool #

length :: Compose * * f g a -> Int #

elem :: Eq a => a -> Compose * * f g a -> Bool #

maximum :: Ord a => Compose * * f g a -> a #

minimum :: Ord a => Compose * * f g a -> a #

sum :: Num a => Compose * * f g a -> a #

product :: Num a => Compose * * f g a -> a #

(Traversable f, Traversable g) => Traversable (Compose * * f g) 

Methods

traverse :: Applicative f => (a -> f b) -> Compose * * f g a -> f (Compose * * f g b) #

sequenceA :: Applicative f => Compose * * f g (f a) -> f (Compose * * f g a) #

mapM :: Monad m => (a -> m b) -> Compose * * f g a -> m (Compose * * f g b) #

sequence :: Monad m => Compose * * f g (m a) -> m (Compose * * f g a) #

Functor f => Generic1 (Compose * * f g) 

Associated Types

type Rep1 (Compose * * f g :: * -> *) :: * -> * #

Methods

from1 :: Compose * * f g a -> Rep1 (Compose * * f g) a #

to1 :: Rep1 (Compose * * f g) a -> Compose * * f g a #

(Eq1 f, Eq1 g) => Eq1 (Compose * * f g) 

Methods

liftEq :: (a -> b -> Bool) -> Compose * * f g a -> Compose * * f g b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (Compose * * f g) 

Methods

liftCompare :: (a -> b -> Ordering) -> Compose * * f g a -> Compose * * f g b -> Ordering #

(Read1 f, Read1 g) => Read1 (Compose * * f g) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Compose * * f g a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Compose * * f g a] #

(Show1 f, Show1 g) => Show1 (Compose * * f g) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose * * f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Compose * * f g a] -> ShowS #

(Alternative f, Applicative g) => Alternative (Compose * * f g) 

Methods

empty :: Compose * * f g a #

(<|>) :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a #

some :: Compose * * f g a -> Compose * * f g [a] #

many :: Compose * * f g a -> Compose * * f g [a] #

(Eq1 f, Eq1 g, Eq a) => Eq (Compose * * f g a) 

Methods

(==) :: Compose * * f g a -> Compose * * f g a -> Bool #

(/=) :: Compose * * f g a -> Compose * * f g a -> Bool #

(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) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall b. b -> c b) -> Compose k1 k f g a -> c (Compose k1 k f g a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose k1 k f g a) #

toConstr :: Compose k1 k f g a -> Constr #

dataTypeOf :: Compose k1 k f g a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Compose k1 k f g a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose k1 k f g a)) #

gmapT :: (forall b. Data b => b -> b) -> Compose k1 k f g a -> Compose k1 k f g a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose k1 k f g a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose k1 k f g a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Compose k1 k f g a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Compose k1 k f g a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Compose k1 k f g a -> m (Compose k1 k f g a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose k1 k f g a -> m (Compose k1 k f g a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose k1 k f g a -> m (Compose k1 k f g a) #

(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) 

Methods

compare :: Compose * * f g a -> Compose * * f g a -> Ordering #

(<) :: Compose * * f g a -> Compose * * f g a -> Bool #

(<=) :: Compose * * f g a -> Compose * * f g a -> Bool #

(>) :: Compose * * f g a -> Compose * * f g a -> Bool #

(>=) :: Compose * * f g a -> Compose * * f g a -> Bool #

max :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a #

min :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a #

(Read1 f, Read1 g, Read a) => Read (Compose * * f g a) 

Methods

readsPrec :: Int -> ReadS (Compose * * f g a) #

readList :: ReadS [Compose * * f g a] #

readPrec :: ReadPrec (Compose * * f g a) #

readListPrec :: ReadPrec [Compose * * f g a] #

(Show1 f, Show1 g, Show a) => Show (Compose * * f g a) 

Methods

showsPrec :: Int -> Compose * * f g a -> ShowS #

show :: Compose * * f g a -> String #

showList :: [Compose * * f g a] -> ShowS #

Generic (Compose k1 k f g a) 

Associated Types

type Rep (Compose k1 k f g a) :: * -> * #

Methods

from :: Compose k1 k f g a -> Rep (Compose k1 k f g a) x #

to :: Rep (Compose k1 k f g a) x -> Compose k1 k f g a #

type Rep1 (Compose * * f g) 
type Rep1 (Compose * * f g) = D1 (MetaData "Compose" "Data.Functor.Compose" "base" True) (C1 (MetaCons "Compose" PrefixI True) (S1 (MetaSel (Just Symbol "getCompose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) f (Rec1 g))))
type Rep (Compose k1 k f g a) 
type Rep (Compose k1 k f g a) = D1 (MetaData "Compose" "Data.Functor.Compose" "base" True) (C1 (MetaCons "Compose" PrefixI True) (S1 (MetaSel (Just Symbol "getCompose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (g a)))))

data Empty f Source #

A rank-2 equivalent of '()', a zero-element tuple

Constructors

Empty 

Instances

DistributiveTraversable k (Empty (k -> *)) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

Distributive k (Empty (k -> *)) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Empty (k -> *)) * f1 f2) Source #

distributeWith :: Functor f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

Applicative k (Empty (k -> *)) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

Apply k (Empty (k -> *)) Source # 

Methods

(<*>) :: g (Arrow (Empty (k -> *)) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

Traversable k (Empty (k -> *)) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Empty (k -> *)) * m p) -> m (g p) Source #

Foldable k (Empty (k -> *)) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

Functor k (Empty (k -> *)) Source # 

Methods

(<$>) :: (forall a. p a -> q a) -> g p -> g q Source #

Eq (Empty k f) Source # 

Methods

(==) :: Empty k f -> Empty k f -> Bool #

(/=) :: Empty k f -> Empty k f -> Bool #

Ord (Empty k f) Source # 

Methods

compare :: Empty k f -> Empty k f -> Ordering #

(<) :: Empty k f -> Empty k f -> Bool #

(<=) :: Empty k f -> Empty k f -> Bool #

(>) :: Empty k f -> Empty k f -> Bool #

(>=) :: Empty k f -> Empty k f -> Bool #

max :: Empty k f -> Empty k f -> Empty k f #

min :: Empty k f -> Empty k f -> Empty k f #

Show (Empty k f) Source # 

Methods

showsPrec :: Int -> Empty k f -> ShowS #

show :: Empty k f -> String #

showList :: [Empty k f] -> ShowS #

newtype Only a f Source #

A rank-2 tuple of only one element

Constructors

Only 

Fields

Instances

DistributiveTraversable k (Only k x) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Only k x) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Only k x) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall a. f1 (f2 a) -> f a) -> f1 (g f2) -> g f Source #

Distributive k (Only k x) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Only k x) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Only k x) * f1 f2) Source #

distributeWith :: Functor f1 => (forall a. f1 (f2 a) -> f a) -> f1 (g f2) -> g f Source #

Applicative k (Only k x) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

Apply k (Only k x) Source # 

Methods

(<*>) :: g (Arrow (Only k x) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

Traversable k (Only k x) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Only k x) * m p) -> m (g p) Source #

Foldable k (Only k x) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

Functor k (Only k a) Source # 

Methods

(<$>) :: (forall b. p b -> q b) -> g p -> g q Source #

Eq (f a) => Eq (Only k a f) Source # 

Methods

(==) :: Only k a f -> Only k a f -> Bool #

(/=) :: Only k a f -> Only k a f -> Bool #

Ord (f a) => Ord (Only k a f) Source # 

Methods

compare :: Only k a f -> Only k a f -> Ordering #

(<) :: Only k a f -> Only k a f -> Bool #

(<=) :: Only k a f -> Only k a f -> Bool #

(>) :: Only k a f -> Only k a f -> Bool #

(>=) :: Only k a f -> Only k a f -> Bool #

max :: Only k a f -> Only k a f -> Only k a f #

min :: Only k a f -> Only k a f -> Only k a f #

Show (f a) => Show (Only k a f) Source # 

Methods

showsPrec :: Int -> Only k a f -> ShowS #

show :: Only k a f -> String #

showList :: [Only k a f] -> ShowS #

newtype Identity g f Source #

Equivalent of Identity for rank 2 data types

Constructors

Identity 

Fields

Instances

DistributiveTraversable k g => DistributiveTraversable k (Identity (k -> *) g) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

Distributive k g => Distributive k (Identity (k -> *) g) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Identity (k -> *) g) * f1 f2) Source #

distributeWith :: Functor f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

Applicative k g => Applicative k (Identity (k -> *) g) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

Apply k g => Apply k (Identity (k -> *) g) Source # 

Methods

(<*>) :: g (Arrow (Identity (k -> *) g) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

Traversable k g => Traversable k (Identity (k -> *) g) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Identity (k -> *) g) * m p) -> m (g p) Source #

Foldable k g => Foldable k (Identity (k -> *) g) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

Functor k g => Functor k (Identity (k -> *) g) Source # 

Methods

(<$>) :: (forall a. p a -> q a) -> g p -> g q Source #

Eq (g f) => Eq (Identity k g f) Source # 

Methods

(==) :: Identity k g f -> Identity k g f -> Bool #

(/=) :: Identity k g f -> Identity k g f -> Bool #

Ord (g f) => Ord (Identity k g f) Source # 

Methods

compare :: Identity k g f -> Identity k g f -> Ordering #

(<) :: Identity k g f -> Identity k g f -> Bool #

(<=) :: Identity k g f -> Identity k g f -> Bool #

(>) :: Identity k g f -> Identity k g f -> Bool #

(>=) :: Identity k g f -> Identity k g f -> Bool #

max :: Identity k g f -> Identity k g f -> Identity k g f #

min :: Identity k g f -> Identity k g f -> Identity k g f #

Show (g f) => Show (Identity k g f) Source # 

Methods

showsPrec :: Int -> Identity k g f -> ShowS #

show :: Identity k g f -> String #

showList :: [Identity k g f] -> ShowS #

data Product g h f Source #

Equivalent of Product for rank 2 data types

Constructors

Pair 

Fields

Instances

(DistributiveTraversable k g, DistributiveTraversable k h) => DistributiveTraversable k (Product (k -> *) g h) Source # 

Methods

collectTraversable :: Traversable f1 => (a -> g f2) -> f1 a -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distributeTraversable :: Traversable f1 => f1 (g f2) -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distributeWithTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

(Distributive k g, Distributive k h) => Distributive k (Product (k -> *) g h) Source # 

Methods

collect :: Functor f1 => (a -> g f2) -> f1 a -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distribute :: Functor f1 => f1 (g f2) -> g (Compose (Product (k -> *) g h) * f1 f2) Source #

distributeWith :: Functor f1 => (forall x. f1 (f2 x) -> f x) -> f1 (g f2) -> g f Source #

(Applicative k g, Applicative k h) => Applicative k (Product (k -> *) g h) Source # 

Methods

pure :: (forall a. f a) -> g f Source #

(Apply k g, Apply k h) => Apply k (Product (k -> *) g h) Source # 

Methods

(<*>) :: g (Arrow (Product (k -> *) g h) p q) -> g p -> g q Source #

liftA2 :: (forall a. p a -> q a -> r a) -> g p -> g q -> g r Source #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> g p -> g q -> g r -> g s Source #

(Traversable k g, Traversable k h) => Traversable k (Product (k -> *) g h) Source # 

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> g p -> m (g q) Source #

sequence :: Applicative m => g (Compose (Product (k -> *) g h) * m p) -> m (g p) Source #

(Foldable k g, Foldable k h) => Foldable k (Product (k -> *) g h) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> g p -> m Source #

(Functor k g, Functor k h) => Functor k (Product (k -> *) g h) Source # 

Methods

(<$>) :: (forall a. p a -> q a) -> g p -> g q Source #

(Eq (h f), Eq (g f)) => Eq (Product k g h f) Source # 

Methods

(==) :: Product k g h f -> Product k g h f -> Bool #

(/=) :: Product k g h f -> Product k g h f -> Bool #

(Ord (h f), Ord (g f)) => Ord (Product k g h f) Source # 

Methods

compare :: Product k g h f -> Product k g h f -> Ordering #

(<) :: Product k g h f -> Product k g h f -> Bool #

(<=) :: Product k g h f -> Product k g h f -> Bool #

(>) :: Product k g h f -> Product k g h f -> Bool #

(>=) :: Product k g h f -> Product k g h f -> Bool #

max :: Product k g h f -> Product k g h f -> Product k g h f #

min :: Product k g h f -> Product k g h f -> Product k g h f #

(Show (h f), Show (g f)) => Show (Product k g h f) Source # 

Methods

showsPrec :: Int -> Product k g h f -> ShowS #

show :: Product k g h f -> String #

showList :: [Product k g h f] -> ShowS #

newtype Arrow p q a Source #

Wrapper for functions that map the argument constructor type

Constructors

Arrow 

Fields

Method synonyms and helper functions

ap :: Apply g => g (Arrow p q) -> g p -> g q Source #

Alphabetical synonym for <*>

fmap :: Functor g => (forall a. p a -> q a) -> g p -> g q Source #

Alphabetical synonym for <$>

liftA3 :: Apply g => (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

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

cotraverse :: (Distributive g, Functor f) => (forall i. f (a i) -> b i) -> f (g a) -> g b Source #

Equivalent of cotraverse for rank 2 data types

cotraverseTraversable :: (DistributiveTraversable g, Traversable f) => (forall i. f (a i) -> b i) -> f (g a) -> g b Source #

Equivalent of cotraverse for rank 2 data types using traversable