barbies-2.0.3.1: Classes for working with types that can change clothes.
Safe HaskellNone
LanguageHaskell2010

Data.Barbie

Description

Deprecated: Use Data.Functor.Barbie or Barbies instead

Synopsis

Functor

class FunctorB (b :: (k -> Type) -> Type) where Source #

Barbie-types that can be mapped over. Instances of FunctorB should satisfy the following laws:

bmap id = id
bmap f . bmap g = bmap (f . g)

There is a default bmap implementation for Generic types, so instances can derived automatically.

Minimal complete definition

Nothing

Methods

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

default bmap :: forall f g. CanDeriveFunctorB b f g => (forall a. f a -> g a) -> b f -> b g Source #

Instances

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

Defined in Barbies.Internal.FunctorB

Methods

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

FunctorB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Void f -> Void g Source #

FunctorB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Unit f -> Unit g Source #

FunctorB (Constant x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Constant x f -> Constant x g Source #

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

Defined in Barbies.Internal.FunctorB

Methods

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

FunctorB b => FunctorB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Barbie b f -> Barbie b g Source #

(FunctorB a, FunctorB b) => FunctorB (Sum a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Sum a b f -> Sum a b g Source #

(FunctorB a, FunctorB b) => FunctorB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Product a b f -> Product a b g Source #

(Functor f, FunctorB b) => FunctorB (Compose f b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f0 a -> g a) -> Compose f b f0 -> Compose f b g Source #

FunctorT b => FunctorB (Flip b f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

bmap :: (forall (a :: k). f0 a -> g a) -> Flip b f f0 -> Flip b f g Source #

Traversable

class FunctorB b => TraversableB (b :: (k -> Type) -> Type) where Source #

Barbie-types that can be traversed from left to right. Instances should satisfy the following laws:

 t . btraverse f   = btraverse (t . f)  -- naturality
btraverse Identity = Identity           -- identity
btraverse (Compose . fmap g . f) = Compose . fmap (btraverse g) . btraverse f -- composition

There is a default btraverse implementation for Generic types, so instances can derived automatically.

Minimal complete definition

Nothing

Methods

btraverse :: Applicative e => (forall a. f a -> e (g a)) -> b f -> e (b g) Source #

default btraverse :: (Applicative e, CanDeriveTraversableB b f g) => (forall a. f a -> e (g a)) -> b f -> e (b g) Source #

Instances

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

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Proxy f -> e (Proxy g) Source #

TraversableB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Void f -> e (Void g) Source #

TraversableB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Unit f -> e (Unit g) Source #

TraversableB (Constant a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Constant a f -> e (Constant a g) Source #

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

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Const a f -> e (Const a g) Source #

TraversableB b => TraversableB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Barbie b f -> e (Barbie b g) Source #

(TraversableB a, TraversableB b) => TraversableB (Sum a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Sum a b f -> e (Sum a b g) Source #

(TraversableB a, TraversableB b) => TraversableB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Product a b f -> e (Product a b g) Source #

(Traversable f, TraversableB b) => TraversableB (Compose f b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a :: k0). f0 a -> e (g a)) -> Compose f b f0 -> e (Compose f b g) Source #

TraversableT b => TraversableB (Flip b f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

btraverse :: Applicative e => (forall (a :: k). f0 a -> e (g a)) -> Flip b f f0 -> e (Flip b f g) Source #

Utility functions

btraverse_ :: (TraversableB b, Applicative e) => (forall a. f a -> e c) -> b f -> e () Source #

Map each element to an action, evaluate these actions from left to right, and ignore the results.

bfoldMap :: (TraversableB b, Monoid m) => (forall a. f a -> m) -> b f -> m Source #

Map each element to a monoid, and combine the results.

bsequence :: (Applicative e, TraversableB b) => b (Compose e f) -> e (b f) Source #

Evaluate each action in the structure from left to right, and collect the results.

bsequence' :: (Applicative e, TraversableB b) => b e -> e (b Identity) Source #

A version of bsequence with f specialized to Identity.

Product

class ApplicativeB b => ProductB (b :: (k -> Type) -> Type) where Source #

Deprecated: Use ApplicativeB

Minimal complete definition

Nothing

Methods

bprod :: b f -> b g -> b (f `Product` g) Source #

default bprod :: CanDeriveProductB b f g => b f -> b g -> b (f `Product` g) Source #

buniq :: (forall a. f a) -> b f Source #

Deprecated: Use bpure

default buniq :: CanDeriveProductB b f f => (forall a. f a) -> b f Source #

Instances

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

Defined in Data.Barbie.Internal.Product

Methods

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Proxy f -> Proxy g -> Proxy (Product f g) Source #

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

ProductB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Unit f -> Unit g -> Unit (Product f g) Source #

buniq :: (forall (a :: k0). f a) -> Unit f Source #

ProductB b => ProductB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Barbie b f -> Barbie b g -> Barbie b (Product f g) Source #

buniq :: (forall (a :: k0). f a) -> Barbie b f Source #

(ProductB a, ProductB b) => ProductB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Product a b f -> Product a b g -> Product a b (Product f g) Source #

buniq :: (forall (a0 :: k0). f a0) -> Product a b f Source #

type CanDeriveProductB b f g = (GenericN (b f), GenericN (b g), GenericN (b (f `Product` g)), GProductB f g (RepN (b f)) (RepN (b g)) (RepN (b (f `Product` g)))) Source #

Utility functions

bzip :: ApplicativeB b => b f -> b g -> b (f `Product` g) Source #

An alias of bprod, since this is like a zip.

bunzip :: ApplicativeB b => b (f `Product` g) -> (b f, b g) Source #

An equivalent of unzip.

bzipWith :: ApplicativeB b => (forall a. f a -> g a -> h a) -> b f -> b g -> b h Source #

An equivalent of zipWith.

bzipWith3 :: ApplicativeB b => (forall a. f a -> g a -> h a -> i a) -> b f -> b g -> b h -> b i Source #

An equivalent of zipWith3.

bzipWith4 :: ApplicativeB b => (forall a. f a -> g a -> h a -> i a -> j a) -> b f -> b g -> b h -> b i -> b j Source #

An equivalent of zipWith4.

Constraints and instance dictionaries

class FunctorB b => ConstraintsB (b :: (k -> Type) -> Type) where Source #

Instances of this class provide means to talk about constraints, both at compile-time, using AllB, and at run-time, in the form of Dict, via baddDicts.

A manual definition would look like this:

data T f = A (f Int) (f String) | B (f Bool) (f Int)

instance ConstraintsB T where
  type AllB c T = (c Int, c String, c Bool)

  baddDicts t = case t of
    A x y -> A (Pair Dict x) (Pair Dict y)
    B z w -> B (Pair Dict z) (Pair Dict w)

Now, when we given a T f, if we need to use the Show instance of their fields, we can use:

baddDicts :: AllB Show b => b f -> b (Dict Show `Product` f)

There is a default implementation of ConstraintsB for Generic types, so in practice one will simply do:

derive instance Generic (T f)
instance ConstraintsB T

Minimal complete definition

Nothing

Associated Types

type AllB (c :: k -> Constraint) b :: Constraint Source #

AllB c b should contain a constraint c a for each a occurring under an f in b f. E.g.:

AllB Show Person ~ (Show String, Show Int)

For requiring constraints of the form c (f a), use AllBF.

type AllB c b = GAll 0 c (GAllRepB b)

Methods

baddDicts :: forall c f. AllB c b => b f -> b (Dict c `Product` f) Source #

default baddDicts :: forall c f. (CanDeriveConstraintsB c b f, AllB c b) => b f -> b (Dict c `Product` f) Source #

Instances

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

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c Proxy Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Proxy => Proxy f -> Proxy (Product (Dict c) f) Source #

ConstraintsB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Void Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Void => Void f -> Void (Product (Dict c) f) Source #

ConstraintsB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Unit Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Unit => Unit f -> Unit (Product (Dict c) f) Source #

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

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Const a) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Const a) => Const a f -> Const a (Product (Dict c) f) Source #

ConstraintsB b => ConstraintsB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Associated Types

type AllB c (Barbie b) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Barbie b) => Barbie b f -> Barbie b (Product (Dict c) f) Source #

(ConstraintsB a, ConstraintsB b) => ConstraintsB (Sum a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Sum a b) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Sum a b) => Sum a b f -> Sum a b (Product (Dict c) f) Source #

(ConstraintsB a, ConstraintsB b) => ConstraintsB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Product a b) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Product a b) => Product a b f -> Product a b (Product (Dict c) f) Source #

(Functor f, ConstraintsB b) => ConstraintsB (Compose f b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Compose f b) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f0 :: k0 -> Type). AllB c (Compose f b) => Compose f b f0 -> Compose f b (Product (Dict c) f0) Source #

type AllBF c f b = AllB (ClassF c f) b Source #

Similar to AllB but will put the functor argument f between the constraint c and the type a. For example:

  AllB  Show   Person ~ (Show    String,  Show    Int)
  AllBF Show f Person ~ (Show (f String), Show (f Int))
  

Utility functions

bmapC :: forall c b f g. (AllB c b, ConstraintsB b) => (forall a. c a => f a -> g a) -> b f -> b g Source #

Like bmap but a constraint is allowed to be required on each element of b

E.g. If all fields of b are Showable then you could store each shown value in it's slot using Const:

showFields :: (AllB Show b, ConstraintsB b) => b Identity -> b (Const String)
showFields = bmapC @Show showField
  where
    showField :: forall a. Show a => Identity a -> Const String a
    showField (Identity a) = Const (show a)

btraverseC :: forall c b f g e. (TraversableB b, ConstraintsB b, AllB c b, Applicative e) => (forall a. c a => f a -> e (g a)) -> b f -> e (b g) Source #

Like btraverse but with a constraint on the elements of b.

Products and constaints

class (ConstraintsB b, ProductB b) => ProductBC (b :: (k -> Type) -> Type) where Source #

Minimal complete definition

Nothing

Methods

bdicts :: AllB c b => b (Dict c) Source #

default bdicts :: (CanDeriveProductBC c b, AllB c b) => b (Dict c) Source #

Instances

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

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: forall (c :: k0 -> Constraint). AllB c Proxy => Proxy (Dict c) Source #

ProductBC (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: forall (c :: k0 -> Constraint). AllB c Unit => Unit (Dict c) Source #

ProductBC b => ProductBC (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: forall (c :: k0 -> Constraint). AllB c (Barbie b) => Barbie b (Dict c) Source #

(ProductBC a, ProductBC b) => ProductBC (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: forall (c :: k0 -> Constraint). AllB c (Product a b) => Product a b (Dict c) Source #

type CanDeriveProductBC c b = (GenericN (b (Dict c)), AllB c b ~ GAll 0 c (GAllRepB b), GProductBC c (GAllRepB b) (RepN (b (Dict c)))) Source #

Utility functions

buniqC :: forall c f b. (AllB c b, ProductBC b) => (forall a. c a => f a) -> b f Source #

Deprecated: Use bpureC instead

bmempty :: forall f b. (AllBF Monoid f b, ConstraintsB b, ApplicativeB b) => b f Source #

Builds a b f, by applying mempty on every field of b.

Wrapper

newtype Barbie (b :: (k -> Type) -> Type) f Source #

A wrapper for Barbie-types, providing useful instances.

Constructors

Barbie 

Fields

Instances

Instances details
FunctorB b => FunctorB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Barbie b f -> Barbie b g Source #

TraversableB b => TraversableB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Barbie b f -> e (Barbie b g) Source #

ApplicativeB b => ApplicativeB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

bpure :: (forall (a :: k0). f a) -> Barbie b f Source #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Barbie b f -> Barbie b g -> Barbie b (Product f g) Source #

ConstraintsB b => ConstraintsB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Associated Types

type AllB c (Barbie b) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Barbie b) => Barbie b f -> Barbie b (Product (Dict c) f) Source #

ProductB b => ProductB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Barbie b f -> Barbie b g -> Barbie b (Product f g) Source #

buniq :: (forall (a :: k0). f a) -> Barbie b f Source #

ProductBC b => ProductBC (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: forall (c :: k0 -> Constraint). AllB c (Barbie b) => Barbie b (Dict c) Source #

(ConstraintsB b, ApplicativeB b, AllBF Semigroup f b) => Semigroup (Barbie b f) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

(<>) :: Barbie b f -> Barbie b f -> Barbie b f #

sconcat :: NonEmpty (Barbie b f) -> Barbie b f #

stimes :: Integral b0 => b0 -> Barbie b f -> Barbie b f #

(ConstraintsB b, ApplicativeB b, AllBF Semigroup f b, AllBF Monoid f b) => Monoid (Barbie b f) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

mempty :: Barbie b f #

mappend :: Barbie b f -> Barbie b f -> Barbie b f #

mconcat :: [Barbie b f] -> Barbie b f #

type AllB (c :: k -> Constraint) (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

type AllB (c :: k -> Constraint) (Barbie b :: (k -> Type) -> Type) = AllB c b

Trivial Barbies

data Void (f :: k -> Type) Source #

Uninhabited barbie type.

Instances

Instances details
FunctorB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Void f -> Void g Source #

TraversableB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Void f -> e (Void g) Source #

ConstraintsB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Void Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Void => Void f -> Void (Product (Dict c) f) Source #

Eq (Void f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

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

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

Ord (Void f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

compare :: Void f -> Void f -> Ordering #

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

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

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

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

max :: Void f -> Void f -> Void f #

min :: Void f -> Void f -> Void f #

Show (Void f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

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

show :: Void f -> String #

showList :: [Void f] -> ShowS #

Generic (Void f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Void f) :: Type -> Type #

Methods

from :: Void f -> Rep (Void f) x #

to :: Rep (Void f) x -> Void f #

Semigroup (Void f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

(<>) :: Void f -> Void f -> Void f #

sconcat :: NonEmpty (Void f) -> Void f #

stimes :: Integral b => b -> Void f -> Void f #

type AllB (c :: k -> Constraint) (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

type AllB (c :: k -> Constraint) (Void :: (k -> Type) -> Type) = GAll 0 c (GAllRepB (Void :: (k -> Type) -> Type))
type Rep (Void f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

type Rep (Void f) = D1 ('MetaData "Void" "Barbies.Internal.Trivial" "barbies-2.0.3.1-GgqTGuuwqazF5i7ulV0eaw" 'False) (V1 :: Type -> Type)

data Unit (f :: k -> Type) Source #

A barbie type without structure.

Constructors

Unit 

Instances

Instances details
FunctorB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Unit f -> Unit g Source #

TraversableB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Unit f -> e (Unit g) Source #

DistributiveB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bdistribute :: forall f (g :: k0 -> Type). Functor f => f (Unit g) -> Unit (Compose f g) Source #

ApplicativeB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bpure :: (forall (a :: k0). f a) -> Unit f Source #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Unit f -> Unit g -> Unit (Product f g) Source #

ConstraintsB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Unit Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Unit => Unit f -> Unit (Product (Dict c) f) Source #

ProductB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Unit f -> Unit g -> Unit (Product f g) Source #

buniq :: (forall (a :: k0). f a) -> Unit f Source #

ProductBC (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: forall (c :: k0 -> Constraint). AllB c Unit => Unit (Dict c) Source #

Eq (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

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

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

(Typeable f, Typeable k) => Data (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

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

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

toConstr :: Unit f -> Constr #

dataTypeOf :: Unit f -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Unit f -> Unit f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unit f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unit f -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> Unit f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unit f -> m (Unit f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit f -> m (Unit f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit f -> m (Unit f) #

Ord (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

compare :: Unit f -> Unit f -> Ordering #

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

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

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

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

max :: Unit f -> Unit f -> Unit f #

min :: Unit f -> Unit f -> Unit f #

Read (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Show (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

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

show :: Unit f -> String #

showList :: [Unit f] -> ShowS #

Generic (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Unit f) :: Type -> Type #

Methods

from :: Unit f -> Rep (Unit f) x #

to :: Rep (Unit f) x -> Unit f #

Semigroup (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

(<>) :: Unit f -> Unit f -> Unit f #

sconcat :: NonEmpty (Unit f) -> Unit f #

stimes :: Integral b => b -> Unit f -> Unit f #

Monoid (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

mempty :: Unit f #

mappend :: Unit f -> Unit f -> Unit f #

mconcat :: [Unit f] -> Unit f #

type AllB (c :: k -> Constraint) (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

type AllB (c :: k -> Constraint) (Unit :: (k -> Type) -> Type) = GAll 0 c (GAllRepB (Unit :: (k -> Type) -> Type))
type Rep (Unit f) Source # 
Instance details

Defined in Barbies.Internal.Trivial

type Rep (Unit f) = D1 ('MetaData "Unit" "Barbies.Internal.Trivial" "barbies-2.0.3.1-GgqTGuuwqazF5i7ulV0eaw" 'False) (C1 ('MetaCons "Unit" 'PrefixI 'False) (U1 :: Type -> Type))

Generic derivations

newtype Rec (p :: Type) a x Source #

Constructors

Rec 

Fields

Instances

Instances details
GTraversable (n :: k1) (f :: k2 -> Type) (g :: k2 -> Type) (Rec a a :: k3 -> Type) (Rec a a :: k3 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Traversable

Methods

gtraverse :: forall t (x :: k). Applicative t => Proxy n -> (forall (a0 :: k). f a0 -> t (g a0)) -> Rec a a x -> t (Rec a a x) Source #

GConstraints n (c :: k1 -> Constraint) (f :: k2) (Rec a' a :: Type -> Type) (Rec b' b :: k3 -> Type) (Rec b' b :: k3 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Constraints

Methods

gaddDicts :: forall (x :: k). GAll n c (Rec a' a) => Rec b' b x -> Rec b' b x Source #

Monoid x => GApplicative (n :: k1) (f :: k2 -> Type) (g :: k2 -> Type) (Rec x x :: k3 -> Type) (Rec x x :: k3 -> Type) (Rec x x :: k3 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Applicative

Methods

gprod :: forall (x0 :: k). Proxy n -> Proxy f -> Proxy g -> Rec x x x0 -> Rec x x x0 -> Rec x x x0 Source #

gpure :: forall (x0 :: k). (f ~ g, Rec x x ~ Rec x x) => Proxy n -> Proxy f -> Proxy (Rec x x) -> Proxy (Rec x x) -> (forall (a :: k). f a) -> Rec x x x0 Source #

GFunctor n (f :: k1 -> Type) (g :: k1 -> Type) (Rec x x :: k2 -> Type) (Rec x x :: k2 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Functor

Methods

gmap :: forall (x0 :: k). Proxy n -> (forall (a :: k). f a -> g a) -> Rec x x x0 -> Rec x x x0 Source #

repbi ~ repbb => GBare n (Rec repbi repbi :: k -> Type) (Rec repbb repbb :: k -> Type) Source # 
Instance details

Defined in Barbies.Generics.Bare

Methods

gstrip :: forall (x :: k0). Proxy n -> Rec repbi repbi x -> Rec repbb repbb x Source #

gcover :: forall (x :: k0). Proxy n -> Rec repbb repbb x -> Rec repbi repbi x Source #

type GAll n (c :: k -> Constraint) (Rec l r :: Type -> Type) Source # 
Instance details

Defined in Barbies.Generics.Constraints

type GAll n (c :: k -> Constraint) (Rec l r :: Type -> Type)

class GProductB (f :: k -> Type) (g :: k -> Type) repbf repbg repbfg where Source #

Methods

gbprod :: Proxy f -> Proxy g -> repbf x -> repbg x -> repbfg x Source #

gbuniq :: (f ~ g, repbf ~ repbg) => Proxy f -> Proxy repbf -> Proxy repbfg -> (forall a. f a) -> repbf x Source #

Instances

Instances details
GProductB (f :: k1 -> Type) (g :: k1 -> Type) (U1 :: k2 -> Type) (U1 :: k2 -> Type) (U1 :: k2 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

gbprod :: forall (x :: k). Proxy f -> Proxy g -> U1 x -> U1 x -> U1 x Source #

gbuniq :: forall (x :: k). (f ~ g, U1 ~ U1) => Proxy f -> Proxy U1 -> Proxy U1 -> (forall (a :: k). f a) -> U1 x Source #

(GProductB f g lf lg lfg, GProductB f g rf rg rfg) => GProductB (f :: k1 -> Type) (g :: k1 -> Type) (lf :*: rf :: k2 -> Type) (lg :*: rg :: k2 -> Type) (lfg :*: rfg :: k2 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

gbprod :: forall (x :: k). Proxy f -> Proxy g -> (lf :*: rf) x -> (lg :*: rg) x -> (lfg :*: rfg) x Source #

gbuniq :: forall (x :: k). (f ~ g, (lf :*: rf) ~ (lg :*: rg)) => Proxy f -> Proxy (lf :*: rf) -> Proxy (lfg :*: rfg) -> (forall (a :: k). f a) -> (lf :*: rf) x Source #

GProductB f g repf repg repfg => GProductB (f :: k1 -> Type) (g :: k1 -> Type) (M1 i c repf :: k2 -> Type) (M1 i c repg :: k2 -> Type) (M1 i c repfg :: k2 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

gbprod :: forall (x :: k). Proxy f -> Proxy g -> M1 i c repf x -> M1 i c repg x -> M1 i c repfg x Source #

gbuniq :: forall (x :: k). (f ~ g, M1 i c repf ~ M1 i c repg) => Proxy f -> Proxy (M1 i c repf) -> Proxy (M1 i c repfg) -> (forall (a :: k). f a) -> M1 i c repf x Source #

class GProductBC c repbx repbd where Source #

Methods

gbdicts :: GAll 0 c repbx => repbd x Source #

Instances

Instances details
GProductBC (c :: k1 -> Constraint) (U1 :: Type -> Type) (U1 :: k2 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

gbdicts :: forall (x :: k). GAll 0 c U1 => U1 x Source #

(GProductBC c lx ld, GProductBC c rx rd) => GProductBC (c :: k1 -> Constraint) (lx :*: rx) (ld :*: rd :: k2 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

gbdicts :: forall (x :: k). GAll 0 c (lx :*: rx) => (ld :*: rd) x Source #

GProductBC c repbx repbd => GProductBC (c :: k1 -> Constraint) (M1 i k3 repbx) (M1 i k3 repbd :: k2 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.ProductC

Methods

gbdicts :: forall (x :: k). GAll 0 c (M1 i k3 repbx) => M1 i k3 repbd x Source #

Deprecations

(/*/) :: ProductB b => b f -> b g -> b (Prod '[f, g]) infixr 4 Source #

Like bprod, but returns a binary Prod, instead of Product, which composes better.

See /*/ for usage.

(/*) :: ProductB b => b f -> b (Prod fs) -> b (Prod (f ': fs)) infixr 4 Source #

Similar to /*/ but one of the sides is already a Prod fs.

Note that /*, /*/ and uncurryn are meant to be used together: /* and /*/ combine b f1, b f2...b fn into a single product that can then be consumed by using uncurryn on an n-ary function. E.g.

f :: f a -> g a -> h a -> i a

bmap (uncurryn f) (bf /* bg /*/ bh)