hkd-records-0.0.1: higher kinded record operations
Safe HaskellNone
LanguageHaskell2010

Data.HKD.Records

Synopsis

Documentation

class FLabels t where Source #

Methods

flabels :: t (Const Text) Source #

get the labels from each field as a (Const Text).

gflabels :: forall t. (Generic (t (Const Text)), GLabels (Rep (t (Const Text)) ())) => t (Const Text) Source #

Automatically derive flabels using generics. This only requires a Generic instance for your datatype.

data Dict c (t :: k) where Source #

Constructors

Dict :: c t => Dict c t

reified type class dictionary. You need to put the constructor in scope in order to use the contained typeclass dictionaries.

class FDicts c t where Source #

Methods

fdicts :: t (Dict c) Source #

hkd record containing the reified type class dictionaries for each field.

gfdicts :: forall t c. (Generic (t (Dict c)), GFDicts (Rep (t (Dict c)) ())) => t (Dict c) Source #

Automatically derive fdict using generics. This only requires a Generic instance for your datatype.

data HkdProd (f :: a -> *) g t Source #

A heterogenous list of higher kinded records. Use :~> to separate the items, and End to terminate them.

Constructors

(t f) :~> (g t) infixr 5 

data LkdProd f g (x :: a) Source #

A heterogenous list of fields. Use :> to separate the items, and End to terminate them.

Constructors

(f x) :> (g x) infixr 5 

data End (t :: k) Source #

The terminator.

fzipManyWith :: (FFunctor t, GFTranspose x t f) => (forall a. f a -> i a) -> x t -> t i Source #

zip over many arguments. The function must take a heterogenous list of fields, separated using :> and terminated by End, while the argument must be a heterogenous list of records, separated by :~>, end terminated by End.

For example:

zipShow :: (FFoldable t, FRepeat t, FLabels t, FDicts Show t, FZip t) =>
           t Identity -> Text
zipShow t =
  Text.concat $
  intersperse "&" $
  ftoList $ 
  fzipManyWith
  ((Identity y :> Const lbl :> Dict :> End) ->
      Const $ lbl <> "=" <> Text.pack (show y))
  (t :~> flabels :~> fdicts @Show :~> End)

ftoList :: FFoldable t => t (Const a) -> [a] Source #

collect (Const) elements into a list efficiently.

type Lens' a s = forall f. Functor f => (a -> f a) -> s -> f s Source #

newtype FLens g s a Source #

A lens for targetting a field of a higher kinded structure. This must be a newtype in order to be partially applied.

Constructors

FLens (Lens' (g a) (s g)) 

class FLenses t where Source #

Methods

flenses :: t (FLens g t) Source #

gflenses :: forall k t r g. GFlensesMachinery k t r g => t (FLens g t) Source #

Autogenerate lenses using generics. You only need to derive Generic for the datatype.