rank2classes-1.4.6: standard type constructor class hierarchy, only with methods of rank 2 types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Rank2

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 infixl 4 Source #

Instances

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

Defined in Rank2

Methods

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

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

Defined in Rank2

Methods

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

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

Defined in Rank2

Methods

(<$>) :: (forall (a :: k0). p a -> q a) -> V1 p -> V1 q 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 #

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 f => Functor (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<$>) :: (forall (a :: k0). p a -> q a) -> Rec1 f p -> Rec1 f 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 (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 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 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 (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Functor f, Functor g) => Functor (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Functor (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<$>) :: (forall (a :: k0). p a -> q a) -> K1 i c p -> K1 i c q Source #

Functor f => Functor (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<$>) :: (forall (a :: k0). p a -> q a) -> M1 i c f p -> M1 i c f q Source #

(Functor g, Functor p) => Functor (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<$>) :: (forall (a :: k0). p0 a -> q a) -> Compose g p p0 -> Compose g p 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 infixl 4 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

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

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). Proxy (p ~> q) -> Proxy p -> Proxy q Source #

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

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

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

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). U1 (p ~> q) -> U1 p -> U1 q Source #

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

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

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

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). V1 (p ~> q) -> V1 p -> V1 q Source #

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

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

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

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 f => Apply (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). Rec1 f (p ~> q) -> Rec1 f p -> Rec1 f q Source #

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

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

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

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 h) => Apply (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 #

(Apply f, Apply g) => Apply (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). (f :*: g) (p ~> q) -> (f :*: g) p -> (f :*: g) q Source #

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

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

Semigroup c => Apply (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). K1 i c (p ~> q) -> K1 i c p -> K1 i c q Source #

liftA2 :: (forall (a :: k0). p a -> q a -> r a) -> K1 i c p -> K1 i c q -> K1 i c r Source #

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

Apply f => Apply (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). M1 i c f (p ~> q) -> M1 i c f p -> M1 i c f q Source #

liftA2 :: (forall (a :: k0). p a -> q a -> r a) -> M1 i c f p -> M1 i c f q -> M1 i c f r Source #

liftA3 :: (forall (a :: k0). p a -> q a -> r a -> s a) -> M1 i c f p -> M1 i c f q -> M1 i c f r -> M1 i c f s Source #

(Apply g, Applicative p) => Apply (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p0 :: k0 -> Type) (q :: k0 -> Type). Compose g p (p0 ~> q) -> Compose g p p0 -> Compose g p q Source #

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

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

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

Defined in Rank2

Methods

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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

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

Defined in Rank2

Methods

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

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 f => Applicative (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

pure :: (forall (a :: k0). f0 a) -> Rec1 f f0 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 (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 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 f, Applicative g) => Applicative (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Semigroup c, Monoid c) => Applicative (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

pure :: (forall (a :: k0). f a) -> K1 i c f Source #

Applicative f => Applicative (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

pure :: (forall (a :: k0). f0 a) -> M1 i c f f0 Source #

(Applicative g, Applicative p) => Applicative (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

pure :: (forall (a :: k0). f a) -> Compose g p 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

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

Defined in Rank2

Methods

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

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

Defined in Rank2

Methods

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

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

Defined in Rank2

Methods

foldMap :: Monoid m => (forall (a :: k0). p a -> m) -> V1 p -> m 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 #

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 f => Foldable (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

foldMap :: Monoid m => (forall (a :: k0). p a -> m) -> Rec1 f 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 (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 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 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 f, Foldable g) => Foldable (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Foldable f, Foldable g) => Foldable (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Foldable (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Foldable f => Foldable (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

foldMap :: Monoid m => (forall (a :: k0). p a -> m) -> M1 i c f p -> m Source #

(Foldable g, Foldable p) => Foldable (Compose g p :: (k -> TYPE LiftedRep) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

Foldable g => Foldable (Flip g a :: (k -> TYPE LiftedRep) -> 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

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

Defined in Rank2

Methods

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

sequence :: forall m (p :: k0 -> Type). Applicative m => Proxy (Compose m p) -> m (Proxy p) Source #

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

Defined in Rank2

Methods

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

sequence :: forall m (p :: k0 -> Type). Applicative m => U1 (Compose m p) -> m (U1 p) Source #

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

Defined in Rank2

Methods

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

sequence :: forall m (p :: k0 -> Type). Applicative m => V1 (Compose m p) -> m (V1 p) 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 :: forall m (p :: k0 -> Type). 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 :: forall m (p :: k0 -> Type). Applicative m => Const x (Compose m p) -> m (Const x p) Source #

Traversable f => Traversable (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: forall m (p :: k0 -> Type). Applicative m => Rec1 f (Compose m p) -> m (Rec1 f 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 :: forall m (p :: k0 -> Type). Applicative m => Identity g (Compose m p) -> m (Identity g 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 :: forall m (p :: k0 -> Type). Applicative m => Only x (Compose m p) -> m (Only x 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 :: forall m (p :: k0 -> Type). Applicative m => Product g h (Compose m p) -> m (Product g h 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 :: forall m (p :: k0 -> Type). Applicative m => Sum g h (Compose m p) -> m (Sum g h p) Source #

(Traversable f, Traversable g) => Traversable (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: forall m (p :: k0 -> Type). Applicative m => (f :*: g) (Compose m p) -> m ((f :*: g) p) Source #

(Traversable f, Traversable g) => Traversable (f :+: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: forall m (p :: k0 -> Type). Applicative m => (f :+: g) (Compose m p) -> m ((f :+: g) p) Source #

Traversable (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: forall m (p :: k0 -> Type). Applicative m => K1 i c (Compose m p) -> m (K1 i c p) Source #

Traversable f => Traversable (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

traverse :: Applicative m => (forall (a :: k0). p a -> m (q a)) -> M1 i c f p -> m (M1 i c f q) Source #

sequence :: forall m (p :: k0 -> Type). Applicative m => M1 i c f (Compose m p) -> m (M1 i c f p) Source #

(Traversable g, Traversable p) => Traversable (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: forall m (p0 :: k0 -> Type). Applicative m => Compose g p (Compose0 m p0) -> m (Compose g p p0) 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 :: forall m (p :: k0 -> Type). 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 p => (a -> g q) -> p a -> g (Compose p q) Source #

distribute :: Functor p => p (g q) -> g (Compose p q) 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

Instances details
Distributive (Proxy :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Proxy q) -> p a -> Proxy (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Proxy q) -> Proxy (Compose p q) Source #

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

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Empty q) -> p a -> Empty (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Empty q) -> Empty (Compose p q) Source #

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

Distributive f => Distributive (Rec1 f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Rec1 f q) -> p a -> Rec1 f (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Rec1 f q) -> Rec1 f (Compose p q) Source #

cotraverse :: Functor m => (forall (a :: k10). m (p a) -> q a) -> m (Rec1 f p) -> Rec1 f q Source #

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Identity g q) -> p a -> Identity g (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Identity g q) -> Identity g (Compose p q) Source #

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

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Only x q) -> p a -> Only x (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Only x q) -> Only x (Compose p q) Source #

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

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Product g h q) -> p a -> Product g h (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Product g h q) -> Product g h (Compose p q) Source #

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

(Distributive f, Distributive g) => Distributive (f :*: g :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> (f :*: g) q) -> p a -> (f :*: g) (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p ((f :*: g) q) -> (f :*: g) (Compose p q) Source #

cotraverse :: Functor m => (forall (a :: k10). m (p a) -> q a) -> m ((f :*: g) p) -> (f :*: g) q Source #

Distributive f => Distributive (M1 i c f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> M1 i c f q) -> p a -> M1 i c f (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (M1 i c f q) -> M1 i c f (Compose p q) Source #

cotraverse :: Functor m => (forall (a :: k10). m (p a) -> q a) -> m (M1 i c f p) -> M1 i c f q Source #

(Distributive g, Distributive p) => Distributive (Compose g p :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collect :: forall p0 a (q :: k10 -> Type). Functor p0 => (a -> Compose g p q) -> p0 a -> Compose g p (Compose0 p0 q) Source #

distribute :: forall p0 (q :: k10 -> Type). Functor p0 => p0 (Compose g p q) -> Compose g p (Compose0 p0 q) Source #

cotraverse :: Functor m => (forall (a :: k10). m (p0 a) -> q a) -> m (Compose g p p0) -> Compose g p q Source #

class Functor g => DistributiveTraversable (g :: (k -> Type) -> Type) 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 #

default cotraverseTraversable :: (Traversable m, Distributive g) => (forall a. m (p a) -> q a) -> m (g p) -> g q Source #

Instances

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

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> Proxy f2) -> f1 a -> Proxy (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). Traversable f1 => f1 (Proxy f2) -> Proxy (Compose f1 f2) Source #

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

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

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> Empty f2) -> f1 a -> Empty (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> Const x f2) -> f1 a -> Const x (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 f => DistributiveTraversable (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> Rec1 f f2) -> f1 a -> Rec1 f (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). Traversable f1 => f1 (Rec1 f f2) -> Rec1 f (Compose f1 f2) Source #

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

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

Defined in Rank2

Methods

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

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 (Only x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 h) => DistributiveTraversable (Product g h :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 #

(DistributiveTraversable f, DistributiveTraversable g) => DistributiveTraversable (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> (f :*: g) f2) -> f1 a -> (f :*: g) (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). Traversable f1 => f1 ((f :*: g) f2) -> (f :*: g) (Compose f1 f2) Source #

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

Monoid c => DistributiveTraversable (K1 i c :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> K1 i c f2) -> f1 a -> K1 i c (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). Traversable f1 => f1 (K1 i c f2) -> K1 i c (Compose f1 f2) Source #

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

DistributiveTraversable f => DistributiveTraversable (M1 i c f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> M1 i c f f2) -> f1 a -> M1 i c f (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). Traversable f1 => f1 (M1 i c f f2) -> M1 i c f (Compose f1 f2) Source #

cotraverseTraversable :: Traversable f1 => (forall (x :: k0). f1 (f2 x) -> f0 x) -> f1 (M1 i c f f2) -> M1 i c f f0 Source #

(DistributiveTraversable g, Distributive p) => DistributiveTraversable (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> Compose g p f2) -> f1 a -> Compose g p (Compose0 f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). Traversable f1 => f1 (Compose g p f2) -> Compose g p (Compose0 f1 f2) Source #

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

class Functor g => Logistic g where Source #

Equivalent of Logistic for rank 2 data types

Methods

deliver :: Contravariant p => p (g q -> g q) -> g (Compose p (q ~> q)) Source #

Instances

Instances details
Logistic (Proxy :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Proxy q -> Proxy q) -> Proxy (Compose p (q ~> q)) Source #

Logistic (Empty :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Empty q -> Empty q) -> Empty (Compose p (q ~> q)) Source #

Logistic f => Logistic (Rec1 f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Rec1 f q -> Rec1 f q) -> Rec1 f (Compose p (q ~> q)) Source #

Logistic g => Logistic (Identity g :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Identity g q -> Identity g q) -> Identity g (Compose p (q ~> q)) Source #

Logistic (Only x :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Only x q -> Only x q) -> Only x (Compose p (q ~> q)) Source #

(Logistic g, Logistic h) => Logistic (Product g h :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Product g h q -> Product g h q) -> Product g h (Compose p (q ~> q)) Source #

(Logistic f, Logistic g) => Logistic (f :*: g :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p ((f :*: g) q -> (f :*: g) q) -> (f :*: g) (Compose p (q ~> q)) Source #

Logistic f => Logistic (M1 i c f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (M1 i c f q -> M1 i c f q) -> M1 i c f (Compose p (q ~> q)) Source #

(Logistic g, Logistic p) => Logistic (Compose g p :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p0 (q :: k10 -> Type). Contravariant p0 => p0 (Compose g p q -> Compose g p q) -> Compose g p (Compose0 p0 (q ~> q)) 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 g p q Source #

Equivalent of Compose for rank 2 data types

Constructors

Compose 

Fields

Instances

Instances details
(Applicative g, Applicative p) => Applicative (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Apply g, Applicative p) => Apply (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

(<*>) :: forall (p0 :: k0 -> Type) (q :: k0 -> Type). Compose g p (p0 ~> q) -> Compose g p p0 -> Compose g p q Source #

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

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

(Distributive g, Distributive p) => Distributive (Compose g p :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collect :: forall p0 a (q :: k10 -> Type). Functor p0 => (a -> Compose g p q) -> p0 a -> Compose g p (Compose0 p0 q) Source #

distribute :: forall p0 (q :: k10 -> Type). Functor p0 => p0 (Compose g p q) -> Compose g p (Compose0 p0 q) Source #

cotraverse :: Functor m => (forall (a :: k10). m (p0 a) -> q a) -> m (Compose g p p0) -> Compose g p q Source #

(DistributiveTraversable g, Distributive p) => DistributiveTraversable (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> Compose g p f2) -> f1 a -> Compose g p (Compose0 f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). Traversable f1 => f1 (Compose g p f2) -> Compose g p (Compose0 f1 f2) Source #

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

(Foldable g, Foldable p) => Foldable (Compose g p :: (k -> TYPE LiftedRep) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Functor g, Functor p) => Functor (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

(Logistic g, Logistic p) => Logistic (Compose g p :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p0 (q :: k10 -> Type). Contravariant p0 => p0 (Compose g p q -> Compose g p q) -> Compose g p (Compose0 p0 (q ~> q)) Source #

(Traversable g, Traversable p) => Traversable (Compose g p :: (k -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

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

sequence :: forall m (p0 :: k0 -> Type). Applicative m => Compose g p (Compose0 m p0) -> m (Compose g p p0) Source #

Show (g (Compose p q)) => Show (Compose g p q) Source # 
Instance details

Defined in Rank2

Methods

showsPrec :: Int -> Compose g p q -> ShowS #

show :: Compose g p q -> String #

showList :: [Compose g p q] -> ShowS #

Eq (g (Compose p q)) => Eq (Compose g p q) Source # 
Instance details

Defined in Rank2

Methods

(==) :: Compose g p q -> Compose g p q -> Bool #

(/=) :: Compose g p q -> Compose g p q -> Bool #

Ord (g (Compose p q)) => Ord (Compose g p q) Source # 
Instance details

Defined in Rank2

Methods

compare :: Compose g p q -> Compose g p q -> Ordering #

(<) :: Compose g p q -> Compose g p q -> Bool #

(<=) :: Compose g p q -> Compose g p q -> Bool #

(>) :: Compose g p q -> Compose g p q -> Bool #

(>=) :: Compose g p q -> Compose g p q -> Bool #

max :: Compose g p q -> Compose g p q -> Compose g p q #

min :: Compose g p q -> Compose g p q -> Compose g p q #

data Empty f Source #

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

Constructors

Empty 

Instances

Instances details
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

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 #

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Empty q) -> p a -> Empty (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Empty q) -> Empty (Compose p q) Source #

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

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

Defined in Rank2

Methods

collectTraversable :: forall f1 a (f2 :: k0 -> Type). Traversable f1 => (a -> Empty f2) -> f1 a -> Empty (Compose f1 f2) Source #

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 #

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 #

Logistic (Empty :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Empty q -> Empty q) -> Empty (Compose p (q ~> q)) 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 :: forall m (p :: k0 -> Type). Applicative m => Empty (Compose m p) -> m (Empty p) Source #

Show (Empty f) Source # 
Instance details

Defined in Rank2

Methods

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

show :: Empty f -> String #

showList :: [Empty f] -> ShowS #

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 #

newtype Only a f Source #

A rank-2 tuple of only one element

Constructors

Only 

Fields

Instances

Instances details
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

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 #

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Only x q) -> p a -> Only x (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Only x q) -> Only x (Compose p q) Source #

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

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

Defined in Rank2

Methods

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

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 #

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 #

Logistic (Only x :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Only x q -> Only x q) -> Only x (Compose p (q ~> q)) 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 :: forall m (p :: k0 -> Type). Applicative m => Only x (Compose m p) -> m (Only x p) Source #

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 #

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 #

newtype Flip g a f Source #

A nested parametric type represented as a rank-2 type

Constructors

Flip 

Fields

Instances

Instances details
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

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 #

Foldable g => Foldable (Flip g a :: (k -> TYPE LiftedRep) -> 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 #

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 :: forall m (p :: k0 -> Type). Applicative m => Flip g a (Compose m p) -> m (Flip g a p) Source #

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 #

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 #

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 #

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 #

newtype Identity g f Source #

Equivalent of Identity for rank 2 data types

Constructors

Identity 

Fields

Instances

Instances details
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

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 #

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Identity g q) -> p a -> Identity g (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Identity g q) -> Identity g (Compose p q) Source #

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

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

Defined in Rank2

Methods

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

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 #

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 #

Logistic g => Logistic (Identity g :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Identity g q -> Identity g q) -> Identity g (Compose p (q ~> q)) 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 :: forall m (p :: k0 -> Type). Applicative m => Identity g (Compose m p) -> m (Identity g p) Source #

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 #

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 #

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

Lifted product of functors.

Constructors

Pair (f a) (g a) 

Instances

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

Defined in Data.Functor.Product

Associated Types

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

Methods

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

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

(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

(<*>) :: forall (p :: k0 -> Type) (q :: k0 -> Type). 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 #

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

Defined in Rank2

Methods

collect :: forall p a (q :: k10 -> Type). Functor p => (a -> Product g h q) -> p a -> Product g h (Compose p q) Source #

distribute :: forall p (q :: k10 -> Type). Functor p => p (Product g h q) -> Product g h (Compose p q) Source #

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

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

Defined in Rank2

Methods

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

distributeTraversable :: forall f1 (f2 :: k0 -> Type). 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 #

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

(Logistic g, Logistic h) => Logistic (Product g h :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Rank2

Methods

deliver :: forall p (q :: k10 -> Type). Contravariant p => p (Product g h q -> Product g h q) -> Product g h (Compose p (q ~> q)) 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 :: forall m (p :: k0 -> Type). Applicative m => Product g h (Compose m p) -> m (Product g h p) Source #

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

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

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

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 #

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

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

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Product f g a -> Product f g a' #

(>$) :: b -> Product f g b -> Product f g 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) #

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

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

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

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

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

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

Defined in Data.Functor.Logistic

Methods

deliver :: Contravariant f0 => f0 (Product f g a -> Product f g a) -> Product f g (f0 (a -> 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) #

(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 :: forall r r'. (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) #

(Monoid (f a), Monoid (g a)) => Monoid (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

mempty :: Product f g a #

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

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

(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

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

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

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

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 #

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

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

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

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

type Rep (Product f g a) = D1 ('MetaData "Product" "Data.Functor.Product" "base" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (g a))))

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

Lifted sum of functors.

Constructors

InL (f a) 
InR (g a) 

Instances

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

Defined in Data.Functor.Sum

Associated Types

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

Methods

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

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

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

(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 :: forall m (p :: k0 -> Type). Applicative m => Sum g h (Compose m p) -> m (Sum g h p) Source #

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

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 #

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

(Contravariant f, Contravariant g) => Contravariant (Sum f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Sum f g a -> Sum f g a' #

(>$) :: b -> Sum f g b -> Sum f g 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) #

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

(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 :: forall r r'. (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) #

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 #

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

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

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

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

($) :: Arrow p q a -> p a -> q a infixr 0 Source #

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 g, Traversable f) => (forall a. f (t a) -> u a) -> f (g t) -> g u Source #

Like fmap, but traverses over its argument

liftA2Traverse1 :: (Apply g, DistributiveTraversable g, Traversable f) => (forall a. f (t a) -> u a -> v a) -> f (g t) -> g u -> g v Source #

Like liftA2, but traverses over its first argument

liftA2Traverse2 :: (Apply g, DistributiveTraversable g, Traversable f) => (forall a. t a -> f (u a) -> v a) -> g t -> f (g u) -> g v Source #

Like liftA2, but traverses over its second argument

liftA2TraverseBoth :: forall f1 f2 g t u v. (Apply g, DistributiveTraversable g, Traversable f1, Traversable f2) => (forall a. f1 (t a) -> f2 (u a) -> v a) -> f1 (g t) -> f2 (g u) -> g 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

getters :: Distributive g => g (Compose ((->) (g f)) f) Source #

Enumerate getters for each element

setters :: Logistic g => g ((f ~> f) ~> Const (g f -> g f)) Source #

Enumerate setters for each element