Copyright | (c) Kristof Bastiaensen 2022 |
---|---|
License | BSD-3 |
Maintainer | kristof@resonata.be |
Stability | stable |
Portability | ghc |
Safe Haskell | None |
Language | Haskell2010 |
Data.HKD.Records
Description
This module contains additions for the hkd package to making it easier
for working with higher kinded records. In particular, it gives
access to the fieldNames of a records using the fieldNames
function,
allows you to zip many records together using fzipManyWith
, and
allows functions with constraints by using the fdicts
function.
This makes it possible to implement many generic functions using these
functions rather than having to implement complicated typeclasses for
Generics. As an example, here is a (poor mans) url encoding function:
zipShow :: (FFoldable t, FRepeat t, FieldNames 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 :~> fieldNames :~> fdicts @Show :~> End)
Synopsis
- class FieldNames t where
- fieldNames :: t (Const Text)
- data Dict c (t :: k) where
- class FDicts c t where
- data RecordCons (f :: a -> *) g t = (t f) :~> (g t)
- data FieldCons f g (x :: a) = (f x) :> (g x)
- data End (t :: k)
- fzipManyWith :: (FFunctor t, GFTranspose x t f) => (forall a. f a -> i a) -> x t -> t i
- ftoList :: FFoldable t => t (Const a) -> [a]
- type Lens' a s = forall f. Functor f => (a -> f a) -> s -> f s
- newtype FLens g s a = FLens (Lens' (g a) (s g))
- class FLenses (t :: (k -> *) -> *) where
Documentation
class FieldNames t where Source #
Minimal complete definition
Nothing
class FDicts c t where Source #
Minimal complete definition
Nothing
Methods
hkd record containing the reified type class dictionaries for
each field. This allows you to use functions with constraints by
combining fdicts
with fzipWith
or fzipManyWith
. Can be
auto derived with a Generic instance.
data RecordCons (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 |
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:
fzipManyWith ((Identity y :> Const lbl :> Dict :> End) -> Const $ lbl <> "=" <> Text.pack (show y)) (t :~> fieldNames :~> fdicts @Show :~> End)
ftoList :: FFoldable t => t (Const a) -> [a] Source #
collect Const
elements into a list efficiently.
A lens for targetting a field of a higher kinded structure. This must be a newtype in order to be partially applied.