rank2classes-0.1: 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 Empty Source # 

Methods

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

Functor g => Functor (Identity g) Source # 

Methods

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

Functor (Only a) Source # 

Methods

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

(Functor g, Functor h) => Functor (Product g h) Source # 

Methods

(<$>) :: (forall a. p a -> q a) -> Product g h p -> Product g h 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

Instances

Apply Empty Source # 

Methods

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

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

Apply g => Apply (Identity g) Source # 

Methods

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

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

Apply (Only x) Source # 

Methods

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

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

(Apply g, Apply h) => Apply (Product g h) Source # 

Methods

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

liftA2 :: (forall a. p a -> q a -> r a) -> Product g h p -> Product g h q -> Product g h r 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 Empty Source # 

Methods

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

Applicative g => Applicative (Identity g) Source # 

Methods

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

Applicative (Only x) Source # 

Methods

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

(Applicative g, Applicative h) => Applicative (Product g h) Source # 

Methods

pure :: (forall a. f a) -> Product g h 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 Empty Source # 

Methods

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

Foldable g => Foldable (Identity g) Source # 

Methods

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

Foldable (Only x) Source # 

Methods

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

(Foldable g, Foldable h) => Foldable (Product g h) Source # 

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> Product g h 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 Empty Source # 

Methods

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

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

Traversable g => Traversable (Identity g) Source # 

Methods

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

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

Traversable (Only x) Source # 

Methods

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

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

(Traversable g, Traversable h) => Traversable (Product g h) Source # 

Methods

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

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

class Functor 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 #

distributeM :: Monad f => f (g f) -> g f Source #

Instances

Distributive Empty Source # 

Methods

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

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

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

distributeM :: Monad f => f (Empty f) -> Empty f Source #

Distributive g => Distributive (Identity g) Source # 

Methods

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

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

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

distributeM :: Monad f => f (Identity g f) -> Identity g f Source #

Distributive (Only x) Source # 

Methods

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

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

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

distributeM :: Monad f => f (Only x f) -> Only x f Source #

(Distributive g, Distributive h) => Distributive (Product g h) Source # 

Methods

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

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

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

distributeM :: Monad f => f (Product g h f) -> Product g h f 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.

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

Distributive Empty Source # 

Methods

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

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

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

distributeM :: Monad f => f (Empty f) -> Empty f Source #

Applicative Empty Source # 

Methods

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

Apply Empty Source # 

Methods

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

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

Traversable Empty Source # 

Methods

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

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

Foldable Empty Source # 

Methods

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

Functor Empty Source # 

Methods

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

Eq (Empty f) Source # 

Methods

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

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

Ord (Empty f) Source # 

Methods

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

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

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

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

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

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

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

Show (Empty f) Source # 

Methods

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

show :: Empty f -> String #

showList :: [Empty f] -> ShowS #

newtype Only a f Source #

A rank-2 tuple of only one element

Constructors

Only 

Fields

Instances

Distributive (Only x) Source # 

Methods

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

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

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

distributeM :: Monad f => f (Only x f) -> Only x f Source #

Applicative (Only x) Source # 

Methods

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

Apply (Only x) Source # 

Methods

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

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

Traversable (Only x) Source # 

Methods

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

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

Foldable (Only x) Source # 

Methods

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

Functor (Only a) Source # 

Methods

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

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

Methods

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

show :: Only a f -> String #

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

newtype Identity g f Source #

Equivalent of Identity for rank 2 data types

Constructors

Identity 

Fields

Instances

Distributive g => Distributive (Identity g) Source # 

Methods

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

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

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

distributeM :: Monad f => f (Identity g f) -> Identity g f Source #

Applicative g => Applicative (Identity g) Source # 

Methods

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

Apply g => Apply (Identity g) Source # 

Methods

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

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

Traversable g => Traversable (Identity g) Source # 

Methods

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

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

Foldable g => Foldable (Identity g) Source # 

Methods

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

Functor g => Functor (Identity g) Source # 

Methods

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

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

Methods

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

show :: Identity g f -> String #

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

data Product g h f Source #

Equivalent of Product for rank 2 data types

Constructors

Pair 

Fields

Instances

(Distributive g, Distributive h) => Distributive (Product g h) Source # 

Methods

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

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

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

distributeM :: Monad f => f (Product g h f) -> Product g h f Source #

(Applicative g, Applicative h) => Applicative (Product g h) Source # 

Methods

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

(Apply g, Apply h) => Apply (Product g h) Source # 

Methods

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

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

(Traversable g, Traversable h) => Traversable (Product g h) Source # 

Methods

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

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

(Foldable g, Foldable h) => Foldable (Product g h) Source # 

Methods

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

(Functor g, Functor h) => Functor (Product g h) Source # 

Methods

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

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

Methods

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

show :: Product g h f -> String #

showList :: [Product 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