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

Safe HaskellNone
LanguageHaskell2010

Barbies

Contents

Description

A common Haskell idiom is to parameterise a datatype by a functor or GADT (or any "indexed type" k -> Type), a pattern sometimes called HKD). This parameter acts like the outfit of a Barbie, turning it into a different doll. The canonical example would be:

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

Let's say that we are writing an application where Person data will be read from a web form, validated, and stored in a database. Some possibles outfits that we could use along the way are:

Person (Const String)  -- for the raw input from the web-form,
Person (Either String) -- for the result of parsing and validating,
Person Identity        -- for the actual data,
Person DbColumn        -- To describe how to read / write a Person to the db

data DbColumn a
  = DbColumn
      { colName :: String
      , fromDb  :: DbDataParser a
      , toDb    :: a -> DbData
      }

In such application it is likely that one will have lots of types like Person so we will like to handle these transformations uniformly, without boilerplate or repetitions. This package provides classes to manipulate these types, using notions that are familiar to haskellers like Functor, Applicative or Traversable. For example, instead of writing an ad-hoc function that checks that all fields have a correct value, like

checkPerson :: Person (Either String) -> Either [String] (Person Identity)

we can write only one such function:

check :: TraversableB b => b (Either String) -> Either [String] (b Identity)
check be
  = case btraverse (either (const Nothing) (Just . Identity)) be of
      Just bi -> Right bi
      Nothing -> Left (bfoldMap (either (:[]) (const [])) be)

Moreover, these classes come with default instances based on Generic, so using them is as easy as:

data Person f
  = Person
      { name :: f String
      , age  :: f Int
      }
  deriving
    ( Generic
    , FunctorB, TraversableB, ApplicativeB, ConstraintsB
    )

deriving instance AllBF Show f Person => Show (Person f)
deriving instance AllBF Eq   f Person => Eq   (Person f)
Synopsis

Barbies are functors

Barbie-types are functors. That means that if one is familiar with standard classes like Functor, Applicative or Traversable, one already knows how to work with barbie-types too. For instance, just like one would use:

fmap f (as :: [a])

to apply f uniformly on every a occurring in as, one could use the following to turn a Either-outfit into Maybe-outfit:

bmap (either (const Nothing) Just) (p :: Person (Either e))

In this case, the argument of bmap will have to be applied on all fields of p:

name p :: Either e String
age  p :: Either e Int

So bmap here demands a polymorphic function of type:

forall a . Either e a -> Maybe a

That is why bmap has a rank-2 type:

bmap :: FunctorB b => (forall a. f a -> g a) -> b f -> b g

Polymorphic functions with Applicative effects can be applied using btraverse and the effects will be accumulated:

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

Finally, some barbie-types (typically records like Person) have an Applicative structure, and allow us to lift pure n-ary functions to functions on barbie-types. For example, bzipWith gives us an analogous of liftA2:

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

We can use this to combine barbies:

addDefaults :: Person Maybe -> Person Identity -> Person Identity
addDefaults = bzipWith (\m d -> maybe d pure m)

Why is there not a MonadB class as well? As everyone knows, a monad is just a monoid in the category of endofunctors, which in this case is a problem, since barbie-types are not endofunctors: they map indexed-types to types, unlike the Functor class, that captures endo-functors on Type.

All these classes, and other convenient functions are found in:

Transformers are functors

Haskellers may be more used to playing with another family of dolls: transformers. Consider for example the following functor-transformers:

Compose g f a
ReaderT r f a
MaybeT f a

Like with barbies, we can think that different choices of f will give us a different doll. And if we start thinking about how to change the outfit of a transformer, we notice that, just like barbie-types, transformer-types are functors too.

tmap :: FunctorT t => (forall a. f a -> g a) -> t f x -> b g x

Where FunctorB captures functors from indexed-types to types, FunctorT captures those between indexed-types. And again, we can identitfy familiar classes of functors: ApplicativeT and TraversableT.

Now, transformers like the ones above, are actually endofunctors, e.g. they map Type -> Type to itself. So it makes sense to classify those that are actually monads: the MonadT class gives us a notion similar to that of MonadTrans, in that it lets us lift a value to its transformed version:

tlift :: MonadT t => f a -> t f a

 -- E.g., using the instance for Compose:
tlift [1, 2, 3] = Compose (Just [1, 2, 3]) :: Compose Maybe [] Int

Unlike all other classes in this package, MonadT instances need to be written by hand.

For further details, see:

Bi-functors and nesting

A barbie-type that is parametric on an additional functor can be made an instance of both FunctorB and FunctorT. For example:

data B f g = B (f Int) (g Bool)
  deriving (Generic)

instance FunctorB (B f)
instance FunctorT B

This gives us a a bifunctor on indexed-types, as we can map simultaneously over both arguments using btmap:

btmap :: (FunctorB (b f), FunctorT b) => (forall a . f a -> f' a) -> (forall a . g a -> g' a) -> b f g -> b f' g'

When f ~ g, we can use a specialized version of btmap:

btmap1 :: (FunctorB (b f), FunctorT b) => (forall a . f a -> f' a) -> b f f -> b f' f'

Functions like btmap1 can be useful to handle cases where we would like a barbie-type to occur under the functor-argument. Let's consider an example of this. Continuing the web form example above, one may want to find out about a person's dependants and model it as follows:

newtype Dependants f
  = Dependants { getDependants :: f [Person f] }

This has the appeal of letting us distinguish two states:

Dependants { getDependants = Just [] }  -- the user declared 0 dependants
Dependants { getDependants = Nothing }  -- the user didn't specify dependants yet

Unfortunately, it is not possible to write a FunctorB instance for such a type (before going on, try to write one yourself!). Intuitively, we would need to have Functor f, which we can't assume. However, such a type can be rewritten as follows:

newtype Dependants f' f
  = Dependants { getDependants :: f' [Person f] }
  deriving (Generic)

instance Functor f' => FunctorB (Dependants f')
instance FunctorT Dependants

type Dependants f = Dependants f f

We can thus use btmap1 as a poor man's version of bmap for Dependants.

For more details, see:

module Barbies.Bi

Container-barbies

Some clothes make barbies look like containers, and we can make those types behave like normal Functors.

newtype Container b a Source #

Wrapper for barbies that act as containers of a by wearing (Const a).

Constructors

Container 

Fields

Instances
FunctorB b => Functor (Container b) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

fmap :: (a -> b0) -> Container b a -> Container b b0 #

(<$) :: a -> Container b b0 -> Container b a #

ApplicativeB b => Applicative (Container b) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

pure :: a -> Container b a #

(<*>) :: Container b (a -> b0) -> Container b a -> Container b b0 #

liftA2 :: (a -> b0 -> c) -> Container b a -> Container b b0 -> Container b c #

(*>) :: Container b a -> Container b b0 -> Container b b0 #

(<*) :: Container b a -> Container b b0 -> Container b a #

TraversableB b => Foldable (Container b) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

fold :: Monoid m => Container b m -> m #

foldMap :: Monoid m => (a -> m) -> Container b a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> Container b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> Container b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> Container b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> Container b a -> b0 #

foldr1 :: (a -> a -> a) -> Container b a -> a #

foldl1 :: (a -> a -> a) -> Container b a -> a #

toList :: Container b a -> [a] #

null :: Container b a -> Bool #

length :: Container b a -> Int #

elem :: Eq a => a -> Container b a -> Bool #

maximum :: Ord a => Container b a -> a #

minimum :: Ord a => Container b a -> a #

sum :: Num a => Container b a -> a #

product :: Num a => Container b a -> a #

TraversableB b => Traversable (Container b) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

traverse :: Applicative f => (a -> f b0) -> Container b a -> f (Container b b0) #

sequenceA :: Applicative f => Container b (f a) -> f (Container b a) #

mapM :: Monad m => (a -> m b0) -> Container b a -> m (Container b b0) #

sequence :: Monad m => Container b (m a) -> m (Container b a) #

Eq (b (Const a :: Type -> Type)) => Eq (Container b a) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

(==) :: Container b a -> Container b a -> Bool #

(/=) :: Container b a -> Container b a -> Bool #

Ord (b (Const a :: Type -> Type)) => Ord (Container b a) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

compare :: Container b a -> Container b a -> Ordering #

(<) :: Container b a -> Container b a -> Bool #

(<=) :: Container b a -> Container b a -> Bool #

(>) :: Container b a -> Container b a -> Bool #

(>=) :: Container b a -> Container b a -> Bool #

max :: Container b a -> Container b a -> Container b a #

min :: Container b a -> Container b a -> Container b a #

Read (b (Const a :: Type -> Type)) => Read (Container b a) Source # 
Instance details

Defined in Barbies.Internal.Containers

Show (b (Const a :: Type -> Type)) => Show (Container b a) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

showsPrec :: Int -> Container b a -> ShowS #

show :: Container b a -> String #

showList :: [Container b a] -> ShowS #

Generic (Container b a) Source # 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (Container b a) :: Type -> Type #

Methods

from :: Container b a -> Rep (Container b a) x #

to :: Rep (Container b a) x -> Container b a #

type Rep (Container b a) Source # 
Instance details

Defined in Barbies.Internal.Containers

type Rep (Container b a) = D1 (MetaData "Container" "Barbies.Internal.Containers" "barbies-2.0.2.0-HfstKv0bfXOCzagLUNTxcB" True) (C1 (MetaCons "Container" PrefixI True) (S1 (MetaSel (Just "getContainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (b (Const a :: Type -> Type)))))

newtype ErrorContainer b e Source #

Wrapper for barbies that act as containers of e by wearing Either e.

Constructors

ErrorContainer 

Fields

Instances
FunctorB b => Functor (ErrorContainer b) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

fmap :: (a -> b0) -> ErrorContainer b a -> ErrorContainer b b0 #

(<$) :: a -> ErrorContainer b b0 -> ErrorContainer b a #

TraversableB b => Foldable (ErrorContainer b) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

fold :: Monoid m => ErrorContainer b m -> m #

foldMap :: Monoid m => (a -> m) -> ErrorContainer b a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> ErrorContainer b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> ErrorContainer b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> ErrorContainer b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> ErrorContainer b a -> b0 #

foldr1 :: (a -> a -> a) -> ErrorContainer b a -> a #

foldl1 :: (a -> a -> a) -> ErrorContainer b a -> a #

toList :: ErrorContainer b a -> [a] #

null :: ErrorContainer b a -> Bool #

length :: ErrorContainer b a -> Int #

elem :: Eq a => a -> ErrorContainer b a -> Bool #

maximum :: Ord a => ErrorContainer b a -> a #

minimum :: Ord a => ErrorContainer b a -> a #

sum :: Num a => ErrorContainer b a -> a #

product :: Num a => ErrorContainer b a -> a #

TraversableB b => Traversable (ErrorContainer b) Source # 
Instance details

Defined in Barbies.Internal.Containers

Methods

traverse :: Applicative f => (a -> f b0) -> ErrorContainer b a -> f (ErrorContainer b b0) #

sequenceA :: Applicative f => ErrorContainer b (f a) -> f (ErrorContainer b a) #

mapM :: Monad m => (a -> m b0) -> ErrorContainer b a -> m (ErrorContainer b b0) #

sequence :: Monad m => ErrorContainer b (m a) -> m (ErrorContainer b a) #

Eq (b (Either e)) => Eq (ErrorContainer b e) Source # 
Instance details

Defined in Barbies.Internal.Containers

Ord (b (Either e)) => Ord (ErrorContainer b e) Source # 
Instance details

Defined in Barbies.Internal.Containers

Read (b (Either e)) => Read (ErrorContainer b e) Source # 
Instance details

Defined in Barbies.Internal.Containers

Show (b (Either e)) => Show (ErrorContainer b e) Source # 
Instance details

Defined in Barbies.Internal.Containers

Generic (ErrorContainer b e) Source # 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (ErrorContainer b e) :: Type -> Type #

Methods

from :: ErrorContainer b e -> Rep (ErrorContainer b e) x #

to :: Rep (ErrorContainer b e) x -> ErrorContainer b e #

type Rep (ErrorContainer b e) Source # 
Instance details

Defined in Barbies.Internal.Containers

type Rep (ErrorContainer b e) = D1 (MetaData "ErrorContainer" "Barbies.Internal.Containers" "barbies-2.0.2.0-HfstKv0bfXOCzagLUNTxcB" True) (C1 (MetaCons "ErrorContainer" PrefixI True) (S1 (MetaSel (Just "getErrorContainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (b (Either e)))))

Wrappers

This can be use with deriving via to automate derivation of instances for Barbie-types.

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 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 :: 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) :: Constraint Source #

Methods

baddDicts :: 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 :: 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 :: 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
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 :: Constraint Source #

Methods

baddDicts :: 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.2.0-HfstKv0bfXOCzagLUNTxcB" 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 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 :: 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 :: 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 :: Constraint Source #

Methods

baddDicts :: 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 :: 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 :: 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 :: (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.2.0-HfstKv0bfXOCzagLUNTxcB" False) (C1 (MetaCons "Unit" PrefixI False) (U1 :: Type -> Type))