| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Barbie
Description
A common Haskell idiom is to parameterise a datatype by a type * -> *,
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, ProofB
)
deriving instance ConstraintsOf Show f Barbie => Show Barbie
deriving instance ConstraintsOf Eq f Barbie => Eq Barbie
Sometimes one wants to use Barbie
and it may feels lik a second-class record type, where one needs to
unpack values in each field. For those cases, we can leverage on
closed type-families ang get the best of both worlds:Identity
dataBaretype familyWearf a whereWearBarea = aWearf a = f a data SignUpForm f = SignUpForm' { username ::WearfString, , password ::WearfString, mailingOk ::WearfBoolean} deriving ( ...,BareB) type SignUpRaw = SignUpFormMaybetype SignUpData = SignUpFormBareformData = SignUpForm "jbond" "shaken007" False :: SignUpData
Synopsis
- class FunctorB b where
- class FunctorB b => TraversableB b where
- bsequence :: (Applicative f, TraversableB b) => b (Compose f g) -> f (b g)
- class FunctorB b => ProductB b where
- (/*/) :: ProductB b => b f -> b g -> b (Prod '[f, g])
- (/*) :: ProductB b => b f -> b (Prod fs) -> b (Prod (f ': fs))
- bzip :: ProductB b => b f -> b g -> b (Product f g)
- bunzip :: ProductB b => b (Product f g) -> (b f, b g)
- bzipWith :: ProductB b => (forall a. f a -> g a -> h a) -> b f -> b g -> b h
- bzipWith3 :: ProductB b => (forall a. f a -> g a -> h a -> i a) -> b f -> b g -> b h -> b i
- 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
- type family Wear f a where ...
- data Bare a
- class FunctorB b => BareB b where
- bstripFrom :: BareB b => (forall a. f a -> a) -> b f -> b Bare
- bcoverWith :: BareB b => (forall a. a -> f a) -> b Bare -> b f
- class FunctorB b => ConstraintsB b where
- type ConstraintsOf (c :: * -> Constraint) (f :: * -> *) b :: Constraint
- class (ConstraintsB b, ProductB b) => ProofB b where
- newtype Barbie b (f :: * -> *) = Barbie {
- getBarbie :: b f
Functor
class FunctorB b where Source #
Barbie-types that can be mapped over. Instances of FunctorB should
satisfy the following laws:
bmapid=idbmapf .bmapg =bmap(f . g)
There is a default bmap implementation for Generic types, so
instances can derived automatically.
Traversable
class FunctorB b => TraversableB b where Source #
Barbie-types that can be traversed from left to right. Instances should satisfy the following laws:
t .btraversef =btraverse(t . f) -- naturalitybtraverseIdentity=Identity-- identitybtraverse(Compose.fmapg . f) =Compose.fmap(btraverseg) .btraversef -- composition
There is a default btraverse implementation for Generic types, so
instances can derived automatically.
Methods
btraverse :: Applicative t => (forall a. f a -> t (g a)) -> b f -> t (b g) Source #
btraverse :: (Applicative t, CanDeriveGenericInstance b) => (forall a. f a -> t (g a)) -> b f -> t (b g) Source #
Instances
| TraversableB b => TraversableB (Barbie b) Source # | |
Defined in Data.Barbie.Internal.Instances | |
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.
Product
class FunctorB b => ProductB b where Source #
Barbie-types that can form products, subject to the laws:
bmap(Paira _) .uncurry.bprod=fstbmap(Pair_ 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} -- has an instance
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, any x :: forall a . f a
determines a unique value of b f, witnessed by the buniq method.
Formally:
const(buniqx) =bmap(constx)
There is a default implementation of bprod and buniq for Generic types,
so instances can derived automatically.
(/*) :: 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 abmap(uncurrynf) (bf/*bg/*/bh)
bunzip :: ProductB b => b (Product f 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.
Bare values
class FunctorB b => BareB b where Source #
Class of Barbie-types defined using Wear and can therefore
have Bare versions. Must satisfy:
bcover.bstrip=idbstrip.bcover=id
bstripFrom :: BareB b => (forall a. f a -> a) -> b f -> b Bare Source #
Generalization of bstrip to arbitrary functors
bcoverWith :: BareB b => (forall a. a -> f a) -> b Bare -> b f Source #
Generalization of bcover to arbitrary functors
Constraints and proofs of instance
class FunctorB b => ConstraintsB b where Source #
Instances of this class provide means to talk about constraints,
both at compile-time, using ConstraintsOf and at run-time,
in the form of class instance dictionaries, via adjProof.
A manual definition would look like this:
data T f = A (fInt) (fString) | B (fBool) (fInt) instanceConstraintsBT where typeConstraintsOfc f T = (c (fInt), c (fString), c (fBool)) adjProof t = case t of A x y -> A (Pair(packDictx) (packDicty)) B z w -> B (Pair(packDictz) (packDictw))
There is a default implementation of ConstraintsOf for
Generic types, so in practice one will simply do:
derive instanceGenericT instanceConstraintsBT
Associated Types
type ConstraintsOf (c :: * -> Constraint) (f :: * -> *) b :: Constraint Source #
should contain a constraint ConstraintsOf c f bc (f x)
for each f x occurring in b. E.g.:
ConstraintsOfShowf Barbie = (Show(fString),Show(fInt))
Methods
adjProof :: forall c f. ConstraintsOf c f b => b f -> b (Product (DictOf c f) f) Source #
Adjoint a proof-of-instance to a barbie-type.
adjProof :: forall c f. (CanDeriveGenericInstance b, ConstraintsOfMatchesGenericDeriv c f b, ConstraintsOf c f b) => b f -> b (Product (DictOf c f) f) Source #
Adjoint a proof-of-instance to a barbie-type.
Instances
| ConstraintsB b => ConstraintsB (Barbie b) Source # | |
Defined in Data.Barbie.Internal.Instances Associated Types type ConstraintsOf c f (Barbie b) :: Constraint Source # | |
class (ConstraintsB b, ProductB b) => ProofB b where Source #
Barbie-types with products have a canonical proof of instance.
There is a default bproof implementation for Generic types, so
instances can derived automatically.
Methods
bproof :: ConstraintsOf c f b => b (DictOf c f) Source #
bproof :: (CanDeriveGenericInstance b, ConstraintsOfMatchesGenericDeriv c f b, ConstraintsOf c f b) => b (DictOf c f) Source #
Wrapper
newtype Barbie b (f :: * -> *) Source #
A wrapper for Barbie-types, providing useful instances.
Instances
| FunctorB b => FunctorB (Barbie b) Source # | |
| TraversableB b => TraversableB (Barbie b) Source # | |
Defined in Data.Barbie.Internal.Instances | |
| ConstraintsB b => ConstraintsB (Barbie b) Source # | |
Defined in Data.Barbie.Internal.Instances Associated Types type ConstraintsOf c f (Barbie b) :: Constraint Source # | |
| BareB b => BareB (Barbie b) Source # | |
| ProductB b => ProductB (Barbie b) Source # | |
| ProofB b => ProofB (Barbie b) Source # | |
Defined in Data.Barbie.Internal.Instances | |
| (ProofB b, ConstraintsOf Semigroup f b) => Semigroup (Barbie b f) Source # | |
| (ProofB b, ConstraintsOf Semigroup f b, ConstraintsOf Monoid f b) => Monoid (Barbie b f) Source # | |
| type ConstraintsOf c f (Barbie b) Source # | |
Defined in Data.Barbie.Internal.Instances | |