barbies-2.0.2.0: Classes for working with types that can change clothes.

Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Prod

Contents

Description

Deprecated: The module is no longer part of the main api and will be removed

Generalize the standard two-functor Product to the product of n-functors. Intuitively, this means:

Product f g a ~~ (f a, g a)

Prod '[]        a ~~  Const () a
Prod '[f]       a ~~ (f a)
Prod '[f, g]    a ~~ (f a, g a)
Prod '[f, g, h] a ~~ (f a, g a, h a)
    ⋮
Synopsis

n-tuples of functors.

data Prod :: [k -> Type] -> k -> Type where Source #

Product of n functors.

Constructors

Unit :: Prod '[] a 
Cons :: f a -> Prod fs a -> Prod (f ': fs) a 
Instances
(Functor f, Functor (Prod fs)) => Functor (Prod (f ': fs)) Source #

Inductively defined instance: Functor (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

fmap :: (a -> b) -> Prod (f ': fs) a -> Prod (f ': fs) b #

(<$) :: a -> Prod (f ': fs) b -> Prod (f ': fs) a #

Functor (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Functor (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

fmap :: (a -> b) -> Prod [] a -> Prod [] b #

(<$) :: a -> Prod [] b -> Prod [] a #

(Applicative f, Applicative (Prod fs)) => Applicative (Prod (f ': fs)) Source #

Inductively defined instance: Applicative (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

pure :: a -> Prod (f ': fs) a #

(<*>) :: Prod (f ': fs) (a -> b) -> Prod (f ': fs) a -> Prod (f ': fs) b #

liftA2 :: (a -> b -> c) -> Prod (f ': fs) a -> Prod (f ': fs) b -> Prod (f ': fs) c #

(*>) :: Prod (f ': fs) a -> Prod (f ': fs) b -> Prod (f ': fs) b #

(<*) :: Prod (f ': fs) a -> Prod (f ': fs) b -> Prod (f ': fs) a #

Applicative (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Applicative (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

pure :: a -> Prod [] a #

(<*>) :: Prod [] (a -> b) -> Prod [] a -> Prod [] b #

liftA2 :: (a -> b -> c) -> Prod [] a -> Prod [] b -> Prod [] c #

(*>) :: Prod [] a -> Prod [] b -> Prod [] b #

(<*) :: Prod [] a -> Prod [] b -> Prod [] a #

(Foldable f, Foldable (Prod fs)) => Foldable (Prod (f ': fs)) Source #

Inductively defined instance: Foldable (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

fold :: Monoid m => Prod (f ': fs) m -> m #

foldMap :: Monoid m => (a -> m) -> Prod (f ': fs) a -> m #

foldr :: (a -> b -> b) -> b -> Prod (f ': fs) a -> b #

foldr' :: (a -> b -> b) -> b -> Prod (f ': fs) a -> b #

foldl :: (b -> a -> b) -> b -> Prod (f ': fs) a -> b #

foldl' :: (b -> a -> b) -> b -> Prod (f ': fs) a -> b #

foldr1 :: (a -> a -> a) -> Prod (f ': fs) a -> a #

foldl1 :: (a -> a -> a) -> Prod (f ': fs) a -> a #

toList :: Prod (f ': fs) a -> [a] #

null :: Prod (f ': fs) a -> Bool #

length :: Prod (f ': fs) a -> Int #

elem :: Eq a => a -> Prod (f ': fs) a -> Bool #

maximum :: Ord a => Prod (f ': fs) a -> a #

minimum :: Ord a => Prod (f ': fs) a -> a #

sum :: Num a => Prod (f ': fs) a -> a #

product :: Num a => Prod (f ': fs) a -> a #

Foldable (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Foldable (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

fold :: Monoid m => Prod [] m -> m #

foldMap :: Monoid m => (a -> m) -> Prod [] a -> m #

foldr :: (a -> b -> b) -> b -> Prod [] a -> b #

foldr' :: (a -> b -> b) -> b -> Prod [] a -> b #

foldl :: (b -> a -> b) -> b -> Prod [] a -> b #

foldl' :: (b -> a -> b) -> b -> Prod [] a -> b #

foldr1 :: (a -> a -> a) -> Prod [] a -> a #

foldl1 :: (a -> a -> a) -> Prod [] a -> a #

toList :: Prod [] a -> [a] #

null :: Prod [] a -> Bool #

length :: Prod [] a -> Int #

elem :: Eq a => a -> Prod [] a -> Bool #

maximum :: Ord a => Prod [] a -> a #

minimum :: Ord a => Prod [] a -> a #

sum :: Num a => Prod [] a -> a #

product :: Num a => Prod [] a -> a #

(Traversable f, Traversable (Prod fs)) => Traversable (Prod (f ': fs)) Source #

Inductively defined instance: Traversable (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Prod (f ': fs) a -> f0 (Prod (f ': fs) b) #

sequenceA :: Applicative f0 => Prod (f ': fs) (f0 a) -> f0 (Prod (f ': fs) a) #

mapM :: Monad m => (a -> m b) -> Prod (f ': fs) a -> m (Prod (f ': fs) b) #

sequence :: Monad m => Prod (f ': fs) (m a) -> m (Prod (f ': fs) a) #

Traversable (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Traversable (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

traverse :: Applicative f => (a -> f b) -> Prod [] a -> f (Prod [] b) #

sequenceA :: Applicative f => Prod [] (f a) -> f (Prod [] a) #

mapM :: Monad m => (a -> m b) -> Prod [] a -> m (Prod [] b) #

sequence :: Monad m => Prod [] (m a) -> m (Prod [] a) #

(Eq1 f, Eq1 (Prod fs)) => Eq1 (Prod (f ': fs)) Source #

Inductively defined instance: Eq1 (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

liftEq :: (a -> b -> Bool) -> Prod (f ': fs) a -> Prod (f ': fs) b -> Bool #

Eq1 (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Eq1 (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

liftEq :: (a -> b -> Bool) -> Prod [] a -> Prod [] b -> Bool #

(Ord1 f, Ord1 (Prod fs)) => Ord1 (Prod (f ': fs)) Source #

Inductively defined instance: Ord1 (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

liftCompare :: (a -> b -> Ordering) -> Prod (f ': fs) a -> Prod (f ': fs) b -> Ordering #

Ord1 (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Ord1 (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

liftCompare :: (a -> b -> Ordering) -> Prod [] a -> Prod [] b -> Ordering #

(Show1 f, Show1 (Prod fs)) => Show1 (Prod (f ': fs)) Source #

Inductively defined instance: Show1 (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Prod (f ': fs) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Prod (f ': fs) a] -> ShowS #

Show1 (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Show1 (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Prod [] a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Prod [] a] -> ShowS #

(Alternative f, Alternative (Prod fs)) => Alternative (Prod (f ': fs)) Source #

Inductively defined instance: Alternative (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

empty :: Prod (f ': fs) a #

(<|>) :: Prod (f ': fs) a -> Prod (f ': fs) a -> Prod (f ': fs) a #

some :: Prod (f ': fs) a -> Prod (f ': fs) [a] #

many :: Prod (f ': fs) a -> Prod (f ': fs) [a] #

Alternative (Prod ([] :: [Type -> Type])) Source #

Inductively defined instance: Alternative (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

empty :: Prod [] a #

(<|>) :: Prod [] a -> Prod [] a -> Prod [] a #

some :: Prod [] a -> Prod [] [a] #

many :: Prod [] a -> Prod [] [a] #

(Eq1 f, Eq a, Eq1 (Prod fs)) => Eq (Prod (f ': fs) a) Source #

Inductively defined instance: Eq (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

(==) :: Prod (f ': fs) a -> Prod (f ': fs) a -> Bool #

(/=) :: Prod (f ': fs) a -> Prod (f ': fs) a -> Bool #

Eq a => Eq (Prod ([] :: [Type -> Type]) a) Source #

Inductively defined instance: Eq (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

(==) :: Prod [] a -> Prod [] a -> Bool #

(/=) :: Prod [] a -> Prod [] a -> Bool #

(Ord1 f, Ord a, Ord1 (Prod fs)) => Ord (Prod (f ': fs) a) Source #

Inductively defined instance: Ord (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

compare :: Prod (f ': fs) a -> Prod (f ': fs) a -> Ordering #

(<) :: Prod (f ': fs) a -> Prod (f ': fs) a -> Bool #

(<=) :: Prod (f ': fs) a -> Prod (f ': fs) a -> Bool #

(>) :: Prod (f ': fs) a -> Prod (f ': fs) a -> Bool #

(>=) :: Prod (f ': fs) a -> Prod (f ': fs) a -> Bool #

max :: Prod (f ': fs) a -> Prod (f ': fs) a -> Prod (f ': fs) a #

min :: Prod (f ': fs) a -> Prod (f ': fs) a -> Prod (f ': fs) a #

Ord a => Ord (Prod ([] :: [Type -> Type]) a) Source #

Inductively defined instance: Ord (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

compare :: Prod [] a -> Prod [] a -> Ordering #

(<) :: Prod [] a -> Prod [] a -> Bool #

(<=) :: Prod [] a -> Prod [] a -> Bool #

(>) :: Prod [] a -> Prod [] a -> Bool #

(>=) :: Prod [] a -> Prod [] a -> Bool #

max :: Prod [] a -> Prod [] a -> Prod [] a #

min :: Prod [] a -> Prod [] a -> Prod [] a #

(Show1 f, Show a, Show1 (Prod fs)) => Show (Prod (f ': fs) a) Source #

Inductively defined instance: Show (Prod (f ': fs)).

Instance details

Defined in Data.Functor.Prod

Methods

showsPrec :: Int -> Prod (f ': fs) a -> ShowS #

show :: Prod (f ': fs) a -> String #

showList :: [Prod (f ': fs) a] -> ShowS #

Show a => Show (Prod ([] :: [Type -> Type]) a) Source #

Inductively defined instance: Show (Prod '[]).

Instance details

Defined in Data.Functor.Prod

Methods

showsPrec :: Int -> Prod [] a -> ShowS #

show :: Prod [] a -> String #

showList :: [Prod [] a] -> ShowS #

zeroTuple :: Prod '[] a Source #

The unit of the product.

oneTuple :: f a -> Prod '[f] a Source #

Lift a functor to a 1-tuple.

fromProduct :: Product f g a -> Prod '[f, g] a Source #

Conversion from a standard Product

toProduct :: Prod '[f, g] a -> Product f g a Source #

Conversion to a standard Product

Flat product of functor products

prod :: Prod ls a -> Prod rs a -> Prod (ls ++ rs) a Source #

Flat product of products.

Lifting functions

uncurryn :: Curried (Prod fs a -> r a) -> Prod fs a -> r a Source #

Like uncurry but using Prod instead of pairs. Can be thought of as a family of functions:

uncurryn :: r a -> Prod '[] a
uncurryn :: (f a -> r a) -> Prod '[f] a
uncurryn :: (f a -> g a -> r a) -> Prod '[f, g] a
uncurryn :: (f a -> g a -> h a -> r a) -> Prod '[f, g, h] a
        ⋮

Type-level helpers

type family l ++ r :: [k] where ... Source #

Type-level, poly-kinded, list-concatenation.

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

type family Curried t where ... Source #

Prod '[f, g, h] a -> r is the type of the uncurried form of a function f a -> g a -> h a -> r. Curried moves from the former to the later. E.g.

Curried (Prod '[]  a    -> r) = r a
Curried (Prod '[f] a    -> r) = f a -> r a
Curried (Prod '[f, g] a -> r) = f a -> g a -> r a

Equations

Curried (Prod '[] a -> r a) = r a 
Curried (Prod (f ': fs) a -> r a) = f a -> Curried (Prod fs a -> r a)