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

Safe HaskellNone
LanguageHaskell2010

Data.Barbie

Contents

Description

A common Haskell idiom is to parameterise a datatype by a type k -> *, typically a functor or a GADT. These are like outfits of a Barbie, that turn her into a different doll. E.g.

data Barbie f
  = Barbie
      { name :: f String
      , age  :: f Int
      }

b1 :: Barbie Last       -- Barbie with a monoid structure
b2 :: Barbie (Const a)  -- Container Barbie
b3 :: Barbie Identity   -- Barbie's new clothes

This module define the classes to work with these types and easily transform them. They all come with default instances based on Generic, so using them is as easy as:

data Barbie f
  = Barbie
      { name :: f String
      , age  :: f Int
      }
  deriving
    ( Generic
    , FunctorB, TraversableB, ProductB, ConstraintsB, ProductBC
    )

deriving instance AllBF Show f Barbie => Show (Barbie f)
deriving instance AllBF Eq   f Barbie => Eq   (Barbie f)

Sometimes one wants to use Barbie Identity and it may feel like a second-class record type, where one needs to unpack values in each field. Data.Barbie.Bare offers a way to have bare versions of a barbie-type.

Notice that all classes in this package are poly-kinded. Intuitively, a barbie is a type parameterised by a functor, and because a barbies is a type of functor, a type parameterised by a barbie is a (higher-kinded) barbie too:

data Catalog b
  = Catalog (b Identity) (b Maybe)
  deriving
    (Generic
    , FunctorB, TraversableB, ProductB, ConstraintsB, ProductBC
    )
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 #

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

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

Defined in Data.Barbie.Internal.Functor

Methods

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

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

Defined in Data.Barbie.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 Data.Barbie.Trivial

Methods

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

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

Defined in Data.Barbie.Internal.Functor

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 Data.Barbie.Internal.Instances

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 Data.Barbie.Internal.Functor

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 Data.Barbie.Internal.Functor

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 Data.Barbie.Internal.Functor

Methods

bmap :: (forall (a :: k0). f0 a -> g a) -> Compose f b f0 -> Compose f b 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 t => (forall a. f a -> t (g a)) -> b f -> t (b g) Source #

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

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

Defined in Data.Barbie.Internal.Traversable

Methods

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

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

Defined in Data.Barbie.Trivial

Methods

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

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

Defined in Data.Barbie.Trivial

Methods

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

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

Defined in Data.Barbie.Internal.Traversable

Methods

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

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

Defined in Data.Barbie.Internal.Instances

Methods

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

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

Defined in Data.Barbie.Internal.Traversable

Methods

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

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

Defined in Data.Barbie.Internal.Traversable

Methods

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

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

Defined in Data.Barbie.Internal.Traversable

Methods

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

Utility functions

btraverse_ :: (TraversableB b, Applicative t) => (forall a. f a -> t c) -> b f -> t () 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 f, TraversableB b) => b (Compose f g) -> f (b g) Source #

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

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

A version of bsequence with g specialized to Identity.

Product

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

Barbie-types that can form products, subject to the laws:

bmap (\(Pair a _) -> a) . uncurry bprod = fst
bmap (\(Pair _ b) -> b) . uncurry bprod = snd

Notice that because of the laws, having an internal product structure is not enough to have a lawful instance. E.g.

data Ok  f = Ok {o1 :: f String, o2 :: f Int}
data Bad f = Bad{b1 :: f String, hiddenFromArg: Int} -- no lawful instance

Intuitively, the laws for this class require that b hides no structure from its argument f. Because of this, if we are given any:

x :: forall a . f a

then this determines a unique value of type b f, witnessed by the buniq method. For example:

buniq x = Ok {o1 = x, o2 = x}

Formally, buniq should satisfy:

const (buniq x) = bmap (const x)

There is a default implementation of bprod and buniq for Generic types, so instances can derived automatically.

Minimal complete definition

Nothing

Methods

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

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

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

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

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

Defined in Data.Barbie.Internal.Product

Methods

bprod :: 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.Trivial

Methods

bprod :: 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.Instances

Methods

bprod :: 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 :: 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 #

Utility functions

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

An alias of bprod, since this is like a zip for Barbie-types.

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

An equivalent of unzip for Barbie-types.

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

An equivalent of zipWith for Barbie-types.

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

An equivalent of zipWith3 for Barbie-types.

bzipWith4 :: ProductB 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 for Barbie-types.

Applicative-like interface

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

Constraints and instance dictionaries

class FunctorB b => ConstraintsB (b :: (k -> *) -> *) 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 if we given a T f, we need to use the Show instance of their fields, we can use:

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

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 Barbie ~ (Show String, Show Int)

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

Methods

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

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

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

Defined in Data.Barbie.Internal.Constraints

Associated Types

type AllB c Proxy :: Constraint Source #

Methods

baddDicts :: AllB c Proxy => Proxy f -> Proxy (Product (Dict c) f) Source #

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

Defined in Data.Barbie.Trivial

Associated Types

type AllB c Void :: Constraint Source #

Methods

baddDicts :: AllB c Void => Void f -> Void (Product (Dict c) f) Source #

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

Defined in Data.Barbie.Trivial

Associated Types

type AllB c Unit :: Constraint Source #

Methods

baddDicts :: AllB c Unit => Unit f -> Unit (Product (Dict c) f) Source #

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

Defined in Data.Barbie.Internal.Constraints

Associated Types

type AllB c (Const a) :: Constraint Source #

Methods

baddDicts :: 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 Data.Barbie.Internal.Instances

Associated Types

type AllB c (Barbie b) :: Constraint Source #

Methods

baddDicts :: 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 Data.Barbie.Internal.Constraints

Associated Types

type AllB c (Sum a b) :: Constraint Source #

Methods

baddDicts :: 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 Data.Barbie.Internal.Constraints

Associated Types

type AllB c (Product a b) :: Constraint Source #

Methods

baddDicts :: 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 Data.Barbie.Internal.Constraints

Associated Types

type AllB c (Compose f b) :: Constraint Source #

Methods

baddDicts :: 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   Barbie ~ (Show    String,  Show    Int)
  AllBF Show f Barbie ~ (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 h. (TraversableB b, ConstraintsB b, AllB c b, Applicative g) => (forall a. c a => f a -> g (h a)) -> b f -> g (b h) 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 #

Every type b that is an instance of both ProductB and ConstraintsB can be made an instance of ProductBC as well.

Intuitively, in addition to buniq from ProductB, one can define buniqC that takes into account constraints:

buniq :: (forall a . f a) -> b f
buniqC :: AllB c b => (forall a . c a => f a) -> b f

For technical reasons, buniqC is not currently provided as a method of this class and is instead defined in terms bdicts, which is similar to baddDicts but can produce the instance dictionaries out-of-the-blue. bdicts could also be defined in terms of buniqC, so they are essentially equivalent.

bdicts :: forall c b . AllB c b => b (Dict c)
bdicts = buniqC (Dict @c)

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

Minimal complete definition

Nothing

Methods

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

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

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

Defined in Data.Barbie.Internal.ProductC

Methods

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

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

Defined in Data.Barbie.Trivial

Methods

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

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

Defined in Data.Barbie.Internal.Instances

Methods

bdicts :: 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 :: AllB c (Product a b) => Product a 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 #

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

bmempty :: forall f b. (AllBF Monoid f b, ProductBC 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
FunctorB b => FunctorB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Instances

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 Data.Barbie.Internal.Instances

Methods

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

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

Defined in Data.Barbie.Internal.Instances

Methods

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

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

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

Defined in Data.Barbie.Internal.Instances

Associated Types

type AllB c (Barbie b) :: Constraint Source #

Methods

baddDicts :: AllB c (Barbie b) => Barbie b f -> Barbie b (Product (Dict c) f) Source #

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

Defined in Data.Barbie.Internal.Instances

Methods

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

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

Defined in Data.Barbie.Internal.Instances

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 #

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

Defined in Data.Barbie.Internal.Instances

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 Data.Barbie.Internal.Instances

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
FunctorB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.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 Data.Barbie.Trivial

Methods

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

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

Defined in Data.Barbie.Trivial

Associated Types

type AllB c Void :: Constraint Source #

Methods

baddDicts :: AllB c Void => Void f -> Void (Product (Dict c) f) Source #

Eq (Void f) Source # 
Instance details

Defined in Data.Barbie.Trivial

Methods

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

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

Ord (Void f) Source # 
Instance details

Defined in Data.Barbie.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 Data.Barbie.Trivial

Methods

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

show :: Void f -> String #

showList :: [Void f] -> ShowS #

Generic (Void f) Source # 
Instance details

Defined in Data.Barbie.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 Data.Barbie.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 Data.Barbie.Trivial

type AllB (c :: k -> Constraint) (Void :: (k -> Type) -> Type) = GAllB c (GAllBRep (Void :: (k -> Type) -> Type))
type Rep (Void f) Source # 
Instance details

Defined in Data.Barbie.Trivial

type Rep (Void f) = D1 (MetaData "Void" "Data.Barbie.Trivial" "barbies-1.1.3.0-CMVVqlu4ofTCwkhij0xzhp" False) (V1 :: Type -> Type)

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

A barbie type without structure.

Constructors

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

Defined in Data.Barbie.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 Data.Barbie.Trivial

Methods

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

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

Defined in Data.Barbie.Trivial

Methods

bprod :: Unit f -> Unit g -> Unit (Product f g) Source #

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

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

Defined in Data.Barbie.Trivial

Associated Types

type AllB c Unit :: Constraint Source #

Methods

baddDicts :: AllB c Unit => Unit f -> Unit (Product (Dict c) f) Source #

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

Defined in Data.Barbie.Trivial

Methods

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

Eq (Unit f) Source # 
Instance details

Defined in Data.Barbie.Trivial

Methods

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

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

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

Defined in Data.Barbie.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 :: (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 Data.Barbie.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 Data.Barbie.Trivial

Show (Unit f) Source # 
Instance details

Defined in Data.Barbie.Trivial

Methods

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

show :: Unit f -> String #

showList :: [Unit f] -> ShowS #

Generic (Unit f) Source # 
Instance details

Defined in Data.Barbie.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 Data.Barbie.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 Data.Barbie.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 Data.Barbie.Trivial

type AllB (c :: k -> Constraint) (Unit :: (k -> Type) -> Type) = GAllB c (GAllBRep (Unit :: (k -> Type) -> Type))
type Rep (Unit f) Source # 
Instance details

Defined in Data.Barbie.Trivial

type Rep (Unit f) = D1 (MetaData "Unit" "Data.Barbie.Trivial" "barbies-1.1.3.0-CMVVqlu4ofTCwkhij0xzhp" False) (C1 (MetaCons "Unit" PrefixI False) (U1 :: Type -> Type))

Generic derivations

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

Constructors

Rec 

Fields

Instances
GConstraintsB (c :: k3 -> Constraint) (f :: k2 -> Type) (Rec a a :: Type -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Constraints

Methods

gbaddDicts :: GAllB c (Rec a a) => Rec a a x -> Rec a a x Source #

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

Defined in Data.Barbie.Internal.Functor

Methods

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

GTraversableB (f :: k2 -> Type) (g :: k2 -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Traversable

Methods

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

GAllBC (Rec a a :: Type -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Constraints

Associated Types

type GAllB c (Rec a a) :: Constraint Source #

repbi ~ repbb => GBareB (Rec repbi repbi :: Type -> Type) (Rec repbb repbb :: Type -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Bare

Methods

gbstrip :: Rec repbi repbi x -> Rec repbb repbb x Source #

gbcover :: Rec repbb repbb x -> Rec repbi repbi x Source #

type GAllB (c :: k -> Constraint) (Rec a a :: Type -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Constraints

type GAllB (c :: k -> Constraint) (Rec a a :: Type -> Type) = ()

Deprecations

type ConstraintsOf c f b = AllBF c f b Source #

Deprecated: Renamed to AllBF (now based on AllB)

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

Deprecated: Renamed to baddDicts

type ProofB b = ProductBC b Source #

Deprecated: Class was renamed to ProductBC

bproof :: forall b c. (ProductBC b, AllB c b) => b (Dict c) Source #

Deprecated: Renamed to bdicts