rank2classes-1.3: standard type constructor class hierarchy, only with methods of rank 2 types

Safe HaskellNone
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, satisfying the usual functor laws

id <$> g == g
(p . q) <$> g == p <$> (q <$> g)

Methods

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

Instances
Functor (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<$>) :: (forall (a0 :: k0). p a0 -> q a0) -> Const a p -> Const a q Source #

Functor (Only a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor g => Functor (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Functor g, Functor h) => Functor (Sum g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Functor g, Functor h) => Functor (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor g => Functor (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

class Functor g => Apply g where Source #

Subclass of Functor halfway to Applicative, satisfying

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

Minimal complete definition

liftA2 | (<*>)

Methods

(<*>) :: g (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 (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

Semigroup x => Apply (Const x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: Const x (p ~> q) -> Const x p -> Const x q Source #

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

liftA3 :: (forall (a :: k0). p a -> q a -> r a -> s a) -> Const x p -> Const x q -> Const x r -> Const x s Source #

Apply (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

liftA3 :: (forall (a :: k0). p a -> q a -> r a -> s a) -> Only x p -> Only x q -> Only x r -> Only x s Source #

Apply g => Apply (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

(Apply g, Apply h) => Apply (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

Applicative g => Apply (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: Flip g a (p ~> q) -> Flip g a p -> Flip g a q Source #

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

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

class Apply g => Applicative g where Source #

Equivalent of Applicative for rank 2 data types

Methods

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

Instances
Applicative (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Semigroup x, Monoid x) => Applicative (Const x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Applicative (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Applicative g => Applicative (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Applicative g, Applicative h) => Applicative (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Applicative g => Applicative (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

class Foldable g where Source #

Equivalent of Foldable for rank 2 data types

Methods

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

Instances
Foldable (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Foldable (Const x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Foldable (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Foldable g => Foldable (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Foldable g, Foldable h) => Foldable (Sum g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Foldable g, Foldable h) => Foldable (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Foldable g => Foldable (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

foldMap :: Monoid m => (forall (a0 :: k0). p a0 -> m) -> Flip g a 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 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

Traversable (Const x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

Traversable (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

traverse :: Applicative m => (forall (a :: k0). 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 (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

traverse :: Applicative m => (forall (a :: k0). 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 g, Traversable h) => Traversable (Sum g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

(Traversable g, Traversable h) => Traversable (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

traverse :: Applicative m => (forall (a :: k0). 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 #

Traversable g => Traversable (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: Applicative m => Flip g a (Compose m p) -> m (Flip g a p) Source #

class DistributiveTraversable g => Distributive g where Source #

Equivalent of Distributive for rank 2 data types

Minimal complete definition

cotraverse | distribute

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 #

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

Instances
Distributive (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Empty p) -> Empty q Source #

Distributive (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Only x p) -> Only x q Source #

Distributive g => Distributive (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Identity g p) -> Identity g q Source #

(Distributive g, Distributive h) => Distributive (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Product g h p) -> Product g h q Source #

class Functor g => DistributiveTraversable (g :: (k -> *) -> *) where Source #

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

Minimal complete definition

Nothing

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 #

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 #

Instances
DistributiveTraversable (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f x) -> f1 (Empty f2) -> Empty f Source #

Monoid x => DistributiveTraversable (Const x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

cotraverseTraversable :: Traversable f1 => (forall (x0 :: k0). f1 (f2 x0) -> f x0) -> f1 (Const x f2) -> Const x f Source #

DistributiveTraversable (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

cotraverseTraversable :: Traversable f1 => (forall (x0 :: k0). f1 (f2 x0) -> f x0) -> f1 (Only x f2) -> Only x f Source #

DistributiveTraversable g => DistributiveTraversable (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

(DistributiveTraversable g, DistributiveTraversable h) => DistributiveTraversable (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f x) -> f1 (Product g h f2) -> Product g h 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 (f :: k -> Type) (g :: k1 -> k) (a :: k1) :: forall k k1. (k -> Type) -> (k1 -> k) -> k1 -> Type 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 => Generic1 (Compose f g :: k -> Type) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep1 (Compose f g) :: k -> Type #

Methods

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

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)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

pure :: a -> Compose f g a #

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

liftA2 :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

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)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

sequenceA :: Applicative f0 => Compose f g (f0 a) -> f0 (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) #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Compose f g a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose f g a] #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

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)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

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] #

(Distributive f, Distributive g) => Distributive (Compose f g) 
Instance details

Defined in Data.Distributive

Methods

distribute :: Functor f0 => f0 (Compose f g a) -> Compose f g (f0 a) #

collect :: Functor f0 => (a -> Compose f g b) -> f0 a -> Compose f g (f0 b) #

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

(Typeable a, Typeable f, Typeable g, Typeable k1, Typeable k2, Data (f (g a))) => Data (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

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

toConstr :: Compose f g a -> Constr #

dataTypeOf :: Compose f g a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

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)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

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)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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

show :: Compose f g a -> String #

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

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: Type -> Type #

Methods

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

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

type Rep1 (Compose f g :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

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

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

type Rep (Compose f g a) = D1 (MetaData "Compose" "Data.Functor.Compose" "base" True) (C1 (MetaCons "Compose" PrefixI True) (S1 (MetaSel (Just "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 (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f x) -> f1 (Empty f2) -> Empty f Source #

Distributive (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Empty p) -> Empty q Source #

Applicative (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Apply (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

Traversable (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

Foldable (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor (Empty :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Eq (Empty f) Source # 
Instance details

Defined in Rank2

Methods

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

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

Ord (Empty f) Source # 
Instance details

Defined in Rank2

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 # 
Instance details

Defined in Rank2

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
DistributiveTraversable (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

cotraverseTraversable :: Traversable f1 => (forall (x0 :: k0). f1 (f2 x0) -> f x0) -> f1 (Only x f2) -> Only x f Source #

Distributive (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Only x p) -> Only x q Source #

Applicative (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Apply (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

liftA3 :: (forall (a :: k0). p a -> q a -> r a -> s a) -> Only x p -> Only x q -> Only x r -> Only x s Source #

Traversable (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

traverse :: Applicative m => (forall (a :: k0). 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 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor (Only a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

Defined in Rank2

Methods

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

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

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

Defined in Rank2

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 # 
Instance details

Defined in Rank2

Methods

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

show :: Only a f -> String #

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

newtype Flip g a f Source #

A nested parametric type represented as a rank-2 type

Constructors

Flip 

Fields

Instances
Applicative g => Applicative (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Applicative g => Apply (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: Flip g a (p ~> q) -> Flip g a p -> Flip g a q Source #

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

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

Traversable g => Traversable (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: Applicative m => Flip g a (Compose m p) -> m (Flip g a p) Source #

Foldable g => Foldable (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor g => Functor (Flip g a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Eq (g (f a)) => Eq (Flip g a f) Source # 
Instance details

Defined in Rank2

Methods

(==) :: Flip g a f -> Flip g a f -> Bool #

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

Ord (g (f a)) => Ord (Flip g a f) Source # 
Instance details

Defined in Rank2

Methods

compare :: Flip g a f -> Flip g a f -> Ordering #

(<) :: Flip g a f -> Flip g a f -> Bool #

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

(>) :: Flip g a f -> Flip g a f -> Bool #

(>=) :: Flip g a f -> Flip g a f -> Bool #

max :: Flip g a f -> Flip g a f -> Flip g a f #

min :: Flip g a f -> Flip g a f -> Flip g a f #

Show (g (f a)) => Show (Flip g a f) Source # 
Instance details

Defined in Rank2

Methods

showsPrec :: Int -> Flip g a f -> ShowS #

show :: Flip g a f -> String #

showList :: [Flip g a f] -> ShowS #

Semigroup (g (f a)) => Semigroup (Flip g a f) Source # 
Instance details

Defined in Rank2

Methods

(<>) :: Flip g a f -> Flip g a f -> Flip g a f #

sconcat :: NonEmpty (Flip g a f) -> Flip g a f #

stimes :: Integral b => b -> Flip g a f -> Flip g a f #

Monoid (g (f a)) => Monoid (Flip g a f) Source # 
Instance details

Defined in Rank2

Methods

mempty :: Flip g a f #

mappend :: Flip g a f -> Flip g a f -> Flip g a f #

mconcat :: [Flip g a f] -> Flip g a f #

newtype Identity g f Source #

Equivalent of Identity for rank 2 data types

Constructors

Identity 

Fields

Instances
DistributiveTraversable g => DistributiveTraversable (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

Distributive g => Distributive (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Identity g p) -> Identity g q Source #

Applicative g => Applicative (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Apply g => Apply (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

Traversable g => Traversable (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

traverse :: Applicative m => (forall (a :: k0). 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 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor g => Functor (Identity g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

Defined in Rank2

Methods

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

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

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

Defined in Rank2

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 # 
Instance details

Defined in Rank2

Methods

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

show :: Identity g f -> String #

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

data Product (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type #

Lifted product of functors.

Constructors

Pair (f a) (g a) 
Instances
Generic1 (Product f g :: k -> Type) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep1 (Product f g) :: k -> Type #

Methods

from1 :: Product f g a -> Rep1 (Product f g) a #

to1 :: Rep1 (Product f g) a -> Product f g a #

(DistributiveTraversable g, DistributiveTraversable h) => DistributiveTraversable (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f x) -> f1 (Product g h f2) -> Product g h f Source #

(Distributive g, Distributive h) => Distributive (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

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 #

cotraverse :: Functor m => (forall (a :: k0). m (p a) -> q a) -> m (Product g h p) -> Product g h q Source #

(Applicative g, Applicative h) => Applicative (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Apply g, Apply h) => Apply (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

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

(Traversable g, Traversable h) => Traversable (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

traverse :: Applicative m => (forall (a :: k0). 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 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Functor g, Functor h) => Functor (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Monad f, Monad g) => Monad (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

(>>=) :: Product f g a -> (a -> Product f g b) -> Product f g b #

(>>) :: Product f g a -> Product f g b -> Product f g b #

return :: a -> Product f g a #

fail :: String -> Product f g a #

(Functor f, Functor g) => Functor (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

fmap :: (a -> b) -> Product f g a -> Product f g b #

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

(MonadFix f, MonadFix g) => MonadFix (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mfix :: (a -> Product f g a) -> Product f g a #

(Applicative f, Applicative g) => Applicative (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

pure :: a -> Product f g a #

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

liftA2 :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c #

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

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

(Foldable f, Foldable g) => Foldable (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

fold :: Monoid m => Product f g m -> m #

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

foldr :: (a -> b -> b) -> b -> Product f g a -> b #

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

foldl :: (b -> a -> b) -> b -> Product f g a -> b #

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

foldr1 :: (a -> a -> a) -> Product f g a -> a #

foldl1 :: (a -> a -> a) -> Product f g a -> a #

toList :: Product f g a -> [a] #

null :: Product f g a -> Bool #

length :: Product f g a -> Int #

elem :: Eq a => a -> Product f g a -> Bool #

maximum :: Ord a => Product f g a -> a #

minimum :: Ord a => Product f g a -> a #

sum :: Num a => Product f g a -> a #

product :: Num a => Product f g a -> a #

(Traversable f, Traversable g) => Traversable (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Product f g a -> f0 (Product f g b) #

sequenceA :: Applicative f0 => Product f g (f0 a) -> f0 (Product f g a) #

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

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

(Eq1 f, Eq1 g) => Eq1 (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

(Ord1 f, Ord1 g) => Ord1 (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

(Read1 f, Read1 g) => Read1 (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Product f g a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Product f g a] #

(Show1 f, Show1 g) => Show1 (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

(MonadZip f, MonadZip g) => MonadZip (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzip :: Product f g a -> Product f g b -> Product f g (a, b) #

mzipWith :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c #

munzip :: Product f g (a, b) -> (Product f g a, Product f g b) #

(Alternative f, Alternative g) => Alternative (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

empty :: Product f g a #

(<|>) :: Product f g a -> Product f g a -> Product f g a #

some :: Product f g a -> Product f g [a] #

many :: Product f g a -> Product f g [a] #

(MonadPlus f, MonadPlus g) => MonadPlus (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzero :: Product f g a #

mplus :: Product f g a -> Product f g a -> Product f g a #

(Distributive f, Distributive g) => Distributive (Product f g) 
Instance details

Defined in Data.Distributive

Methods

distribute :: Functor f0 => f0 (Product f g a) -> Product f g (f0 a) #

collect :: Functor f0 => (a -> Product f g b) -> f0 a -> Product f g (f0 b) #

distributeM :: Monad m => m (Product f g a) -> Product f g (m a) #

collectM :: Monad m => (a -> Product f g b) -> m a -> Product f g (m b) #

(Eq1 f, Eq1 g, Eq a) => Eq (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

(Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Product f g a -> c (Product f g a) #

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

toConstr :: Product f g a -> Constr #

dataTypeOf :: Product f g a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Product f g a)) #

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

gmapT :: (forall b. Data b => b -> b) -> Product f g a -> Product f g a #

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

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

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

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

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

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

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

(Ord1 f, Ord1 g, Ord a) => Ord (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

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

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

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

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

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

(Read1 f, Read1 g, Read a) => Read (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

readList :: ReadS [Product f g a] #

readPrec :: ReadPrec (Product f g a) #

readListPrec :: ReadPrec [Product f g a] #

(Show1 f, Show1 g, Show a) => Show (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

show :: Product f g a -> String #

showList :: [Product f g a] -> ShowS #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type #

Methods

from :: Product f g a -> Rep (Product f g a) x #

to :: Rep (Product f g a) x -> Product f g a #

type Rep1 (Product f g :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

type Rep (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

data Sum (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type #

Lifted sum of functors.

Constructors

InL (f a) 
InR (g a) 
Instances
Generic1 (Sum f g :: k -> Type) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep1 (Sum f g) :: k -> Type #

Methods

from1 :: Sum f g a -> Rep1 (Sum f g) a #

to1 :: Rep1 (Sum f g) a -> Sum f g a #

(Traversable g, Traversable h) => Traversable (Sum g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

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

(Foldable g, Foldable h) => Foldable (Sum g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Functor g, Functor h) => Functor (Sum g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Functor f, Functor g) => Functor (Sum f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

fmap :: (a -> b) -> Sum f g a -> Sum f g b #

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

(Foldable f, Foldable g) => Foldable (Sum f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

fold :: Monoid m => Sum f g m -> m #

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

foldr :: (a -> b -> b) -> b -> Sum f g a -> b #

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

foldl :: (b -> a -> b) -> b -> Sum f g a -> b #

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

foldr1 :: (a -> a -> a) -> Sum f g a -> a #

foldl1 :: (a -> a -> a) -> Sum f g a -> a #

toList :: Sum f g a -> [a] #

null :: Sum f g a -> Bool #

length :: Sum f g a -> Int #

elem :: Eq a => a -> Sum f g a -> Bool #

maximum :: Ord a => Sum f g a -> a #

minimum :: Ord a => Sum f g a -> a #

sum :: Num a => Sum f g a -> a #

product :: Num a => Sum f g a -> a #

(Traversable f, Traversable g) => Traversable (Sum f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Sum f g a -> f0 (Sum f g b) #

sequenceA :: Applicative f0 => Sum f g (f0 a) -> f0 (Sum f g a) #

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

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

(Eq1 f, Eq1 g) => Eq1 (Sum f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

(Ord1 f, Ord1 g) => Ord1 (Sum f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

(Read1 f, Read1 g) => Read1 (Sum f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum f g a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum f g a] #

(Show1 f, Show1 g) => Show1 (Sum f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

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

(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

(==) :: Sum f g a -> Sum f g a -> Bool #

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

(Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Sum f g a -> c (Sum f g a) #

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

toConstr :: Sum f g a -> Constr #

dataTypeOf :: Sum f g a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum f g a)) #

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

gmapT :: (forall b. Data b => b -> b) -> Sum f g a -> Sum f g a #

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

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

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

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

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

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

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

(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

compare :: Sum f g a -> Sum f g a -> Ordering #

(<) :: Sum f g a -> Sum f g a -> Bool #

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

(>) :: Sum f g a -> Sum f g a -> Bool #

(>=) :: Sum f g a -> Sum f g a -> Bool #

max :: Sum f g a -> Sum f g a -> Sum f g a #

min :: Sum f g a -> Sum f g a -> Sum f g a #

(Read1 f, Read1 g, Read a) => Read (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

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

readList :: ReadS [Sum f g a] #

readPrec :: ReadPrec (Sum f g a) #

readListPrec :: ReadPrec [Sum f g a] #

(Show1 f, Show1 g, Show a) => Show (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

showsPrec :: Int -> Sum f g a -> ShowS #

show :: Sum f g a -> String #

showList :: [Sum f g a] -> ShowS #

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: Type -> Type #

Methods

from :: Sum f g a -> Rep (Sum f g a) x #

to :: Rep (Sum f g a) x -> Sum f g a #

type Rep1 (Sum f g :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

type Rep (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

newtype Arrow p q a Source #

Wrapper for functions that map the argument constructor type

Constructors

Arrow 

Fields

type (~>) = Arrow infixr 0 Source #

Method synonyms and helper functions

fst :: Product g h p -> g p Source #

Helper function for accessing the first field of a Pair

snd :: Product g h p -> h p Source #

Helper function for accessing the second field of a Pair

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

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