barbies-2.0.4.0: Classes for working with types that can change clothes.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Barbies.Bare

Description

Sometimes one needs a type like Barbie Identity and it may feel like a second-class record type, where one needs to unpack values in each field. For those cases, we can leverage on closed type-families:

data Bare
data Covered

type family Wear t f a where
  Wear Bare    f a = a
  Wear Covered f a = f a

data SignUpForm t f
  = SignUpForm
      { username  :: Wear t f String,
      , password  :: Wear t f String
      , mailingOk :: Wear t f Bool
      }
 instance FunctorB (SignUpForm Covered)
 instance TraversableB (SignUpForm Covered)
 ...,
 instance BareB SignUpForm

type SignUpRaw  = SignUpForm Covered Maybe
type SignUpData = SignUpForm Bare Identity

formData = SignUpForm "jbond" "shaken007" False :: SignUpData
Synopsis

Bare values

type family Wear t f a where ... Source #

The Wear type-function allows one to define a Barbie-type as

data B t f
  = B { f1 :: Wear t f Int
      , f2 :: Wear t f Bool
      }

This gives rise to two rather different types:

  • B Covered f is a normal Barbie-type, in the sense that f1 :: B Covered f -> f Int, etc.
  • B Bare f, on the other hand, is a normal record with no functor around the type:
B { f1 :: 5, f2 = True } :: B Bare f

Equations

Wear Bare f a = a 
Wear Covered f a = f a 
Wear (Param _ t) f a = Wear t f a 
Wear t _ _ = TypeError (('Text "`Wear` should only be used with " :<>: 'Text "`Bare` or `Covered`.") :$$: ((('Text "`" :<>: 'ShowType t) :<>: 'Text "`") :<>: 'Text " is not allowed in this context.")) 

Covering and stripping

class FunctorB (b Covered) => BareB b where Source #

Class of Barbie-types defined using Wear and can therefore have Bare versions. Must satisfy:

bcover . bstrip = id
bstrip . bcover = id

Minimal complete definition

Nothing

bstripFrom :: BareB b => (forall a. f a -> a) -> b Covered f -> b Bare Identity Source #

Generalization of bstrip to arbitrary functors

bcoverWith :: BareB b => (forall a. a -> f a) -> b Bare Identity -> b Covered f Source #

Generalization of bcover to arbitrary functors

type family WearTwo t f g a where ... Source #

Like the Wear family, but with two wrappers f and g instead of one. This is useful if you have a data-type where f is parametric but g is not, consider this:

data T t f =
  T { f1 :: Wear    t f [Bool]
    , f2 :: Wear    t f (Sum Int)
    , f3 :: WearTwo t f Sum Int
    , f4 :: WearTwo t f Max Int
    }

with x :: T Covered Option we would have

f1 x :: IO (Option [Bool])
f2 x :: IO (Option (Sum Int))
f3 x :: IO (Option (Sum Int))
f4 x :: IO (Option (Max Int))

and with y :: T Bare Identity we would have

f1 y :: Int
f2 y :: Sum Int
f3 y :: Int
f4 y :: Int

Note how (Option (Sum Int)) (or Max) has a nice Semigroup instance that we can use to merge two (covered) barbies, while WearTwo removes the wrapper for the bare barbie.

Equations

WearTwo Bare f g a = a 
WearTwo Covered f g a = f (g a) 
WearTwo (Param _ t) f g a = WearTwo t f g a 
WearTwo t _ _ _ = TypeError (('Text "`WearTwo` should only be used with " :<>: 'Text "`Bare` or `Covered`.") :$$: ((('Text "`" :<>: 'ShowType t) :<>: 'Text "`") :<>: 'Text " is not allowed in this context."))