hkd-records-0.0.4: higher kinded record operations
Copyright(c) Kristof Bastiaensen 2022
LicenseBSD-3
Maintainerkristof@resonata.be
Stabilitystable
Portabilityghc
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Documentation

class FieldNames t where Source #

Minimal complete definition

Nothing

Methods

fieldNames :: t (Const Text) Source #

get the fieldNames from each field as a (Const Text). Can be auto derived for records with a Generic instance.

default fieldNames :: (Generic (t (Const Text)), GFieldNames (Rep (t (Const Text)) ())) => t (Const Text) Source #

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

Constructors

Dict :: c t => Dict c t

reified type class dictionary. You can use the contained typeclass by putting the Dict constructor somewhere within scope. Can be auto derived with a Generic instance.

class FDicts c t where Source #

Minimal complete definition

Nothing

Methods

fdicts :: t (Dict c) Source #

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.

default fdicts :: (Generic (t (Dict c)), GFDicts (Rep (t (Dict c)) ())) => t (Dict c) Source #

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 

data FieldCons 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.

Constructors

End 

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.

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 :: (k -> *) -> *) where Source #

Minimal complete definition

Nothing

Methods

flenses :: t (FLens g t) Source #

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