Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.HKD.Records
Synopsis
- class FLabels t where
- gflabels :: forall t. (Generic (t (Const Text)), GLabels (Rep (t (Const Text)) ())) => t (Const Text)
- data Dict c (t :: k) where
- class FDicts c t where
- gfdicts :: forall t c. (Generic (t (Dict c)), GFDicts (Rep (t (Dict c)) ())) => t (Dict c)
- data HkdProd (f :: a -> *) g t = (t f) :~> (g t)
- data LkdProd 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 where
- gflenses :: forall k t r g. GFlensesMachinery k t r g => t (FLens g t)
Documentation
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.
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 |
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.
A lens for targetting a field of a higher kinded structure. This must be a newtype in order to be partially applied.