HKD: best or worst thing ever?

Many uses of HKD in the wild are only ever used to toggle between Maybe and Identity, or NonEmpty and Identity—simple cardinality restrictions, in other words. In such cases, I tend to favor the following lower-kinded approach for its simplicity:

-- For toggling between 0-or-1 and exactly-1:
data Foo opt = Foo {
  field1 :: Either opt Int,
  field2 :: Either opt String,
  field3 :: Either opt Bool
}
type FooOptionally = Foo ()
type FooDefinitely = forall a. Foo a

-- For toggling between 1-or-more and exactly-1:
data MaybeMore more a = MaybeMore a (Maybe (more, NonEmpty a))
  deriving Functor
data Foo more = Foo {
  field1 :: MaybeMore more Int,
  field2 :: MaybeMore more String,
  field3 :: MaybeMore more Bool
}
type FooPlural = Foo ()
type FooSingular = forall a. Foo a


-- Some helper patterns I usually use for matching on these things:

pattern CompletelyRight :: a -> Either Void a
pattern CompletelyRight a <- (either absurd id -> a)
  where CompletelyRight a = Right a
{-# COMPLETE CompletelyRight #-}

pattern It'sNothing :: Maybe (Void, a)
pattern It'sNothing <- (maybe () (absurd . fst) -> ())
  where It'sNothing = Nothing
{-# COMPLETE It'sNothing #-}

This avoids both giant sum types and representable invalid states, sometimes at the cost of a little extra boxing relative to HKD. It’s pretty manageable.

And how could I forget to mention the best part: the exactly-1 case is a true subtype of the others, as it intuitively ought to be! No conversion, not even a coerce, is necessary to use a FooDefinitely value where FooOptionally is desired. Try that with HKD.

7 Likes

I’ll add a voice to the “pro-type families” crowd.

“Strict HKD” – as in, using type constructors – is often too limited to be of much use IME. Either you are restricted to each field using the same type constructor (sacrificing flexibility), or you load up your type with multiple type vars for different constructors as needed (sacrificing ergonomics).

Indexing your type with type families (Trees that Grow), however, is a whole different game. It’s a powerful technique, and shouldn’t be the first thing you reach for, but it can be quite nice when you have several large data types that have nearly identical fields, save for differences on a per-field basis.

I haven’t used any libraries for it though, just rolled my own.

3 Likes

The win, I find, is not when looking at the code as an artifact. Rather, I think the win resides around the engineering process of defining field names once in a way that translates the “ad-hoc REST” description of the service I interact with. For my ACME lib, the typical description is rfc-8555. The exact set of fields present in various API calls is somewhere between hard to parse and undocumented (and thus subtle difference could occur depending on the interpretations at different server). One could lament that such specs are not formal enough, but this RFC illustrates well what we have to deal with in the wild. Of course the value of the approach boils down to preference, but I value a lot a code structure which lets me “map the spec into some type” first and then in another place restrict/depart/adapt/refine in an extensible way. That’s why I picked a blunderbuss Field definition which allows to entirely replace the field-type but stills enables a way to convey and start from the information “this is the canonical type if we read the spec”.

1 Like

Not sure if this is a valid use-case, but I gave HKD a try to let the caller pick between [] and Vector when fetching remote data. For what it’s worth, here is the change.

1 Like

It’s certainly valid to call this HKD, but is it HKD according to the pattern we see prescribed by barbies and other libraries? Parameterizing a record by a type constructor is a general pattern, but sometimes we say HKD when we mean every field is wrapped in that type constructor – i.e. the “template” type to which @mixphix refers.

Although I think even this usage can be loosened. Consider Data.Functor.Barbie from barbies, which says each field must be wrapped by the type constructor or must be a Monoid.

1 Like

I piddled about with a similar idea for forms with HKD here Indexed fields exploration · GitHub (in which I created this cool new technique that everyone had already been using for years… :slight_smile: ), I think that’s not been explored much because the web shifted from backend to frontend in the 2010s, so a lot of formlets innovation just stopped. And yesod-form was always a brutally simplified type of formlet. Amusingly all this great insight gained in the Haskell world was ignored while the React world decided to reinvent forms all over again and do it badly.

Inadvisedly I continued working on it with GitHub - chrisdone-archive/forge: Haskell form library as my vehicle, which does address optional vs required fields at the type-level and is quite ergonomic. I also implemented error information flow that goes both upwards and downwards (“floor” and “ceiling”), which I consider novel in the design space, and based on practical need.

Reflex happened since then, which was a bit of a game changer.

I’m generally unconvinced that tying a form’s shape to a record is as flexible as it needs to be in practice, it’s an idea that sounds good on paper but later feels constraining. I did in PureScript because you can do such things easily with records in PureScript and realized it is a very modest win.

Now that Htmx is popular and plain old web backends are in vogue again, we might see a resurgence in formlets as an abstraction and new ideas come up (e.g. using Selective (my “BindForm”) or other things).

2 Likes

Disclaimer: I won’t use HKD in the stricter all fields wrapped in the same rank-1 parameter sense.
One aspect that I, like @mixphix, believe could be a great source of convenience is when HKD is used to define both the data structure and its parsers/forms. The hard part is then to define sensible “glue” that traverses the structure Parser to form a Parser (structure Identity). I have not seen a convincing companion data type that can be used to describe “the space between the fields of a record”, which any sensible UI designer would want fine control over. I believe the difficulty of finding good “glue” is also what @chrisdone observed. An alternative, but even less flexible way, is going via type classes like in aeson or in this experiment. That also suffers from the glue problem, this time in the type class instance deriving.

For business logic I found myself using HKD to unify nearly-identical data structures in the Trees That Grow fashion:

-- before:
class HasHeader t where header :: t -> Hdr
data Transaction  = T   {tHeader  :: Hdr, tPayload   :: Playload}
data Transactions = Ts  {tsHeader :: Hdr, tsPayload :: [Playload],  check :: String}
-- after:
data Transaction' f c = T' {header :: Hdr, payload :: f Payload, check :: c}
type Transaction  = Transaction' Identity ()
type Transactions = Transaction' [] String

Unifying data structures this way in an existing code base can be done with little code change, but thereafter remembering the exact definition of all the type aliases puts extra mental burden on the maintainer.
Upside: Extensible Records in Haskell98 without any language extentions like OverloadedLabels or TypeFamilies. Downside: For HKDs like the above, the standard deriving strategies usually fail, so you have to write more boilerplate. Would I do it again if I were to write all the code from scratch? Probably no.

2 Likes

Standalone deriving doesn’t work with those? Like, deriving stock Show would work if you bring the constraints. Unless that’s the boilerplate you’re referring to :sweat_smile:

I’m honing in on such a “glue” for Yesod.Form that will work for any Record type. With some minor adjustments to the data structures and the clever composition of Applicative Functors, we end up with a transformation

form :: forall ty. FormEntry app ty -> Compose (FormFor app) (FormExit app) ty

where FormEntry is the data necessary for creating a DOM element/parsing the request, FormExit app ty ~ (FormResult ty, WidgetFor app ()), and FormFor app is the same RWST monad but parameterized by the appropriate app variable (rather than an abstract, convoluted MonadHandler m). The functors on both sides of the function arrow are Applicative, so for a Prairie.Record we have

newtype Tabulate rec f = Tabulate (Field rec ~> f)

idIso :: (Record rec) => Iso' rec (Tabulate rec Identity)
idIso = iso (distribute . Identity) (runIdentity . tabulate)

distribute :: (Record rec, Functor f) => f rec -> Tabulate rec f
distribute frec = Tabulate \field -> getRecordField field <$> frec

tabulate :: (Record rec, Applicative f) => Tabulate rec f -> f rec
tabulate (Tabulate f) = tabulateRecordA f

components :: (Record rec) => f ~> g -> Tabulate rec f -> Tabulate rec g
components nat (Tabulate f) = Tabulate (nat . f)

-- data Entry app ty is the elided, adjusted Yesod.Form.Field equivalent
-- data FormEntry app ty = FormEntry (Entry app ty) [(Text, Text)] ty
type FormEntry app =
  Product
    (Entry app)
    (Product (Const [(Text, Text)]) Identity)
-- data FormExit app ty = FormExit (FormResult ty) (WidgetFor app ())
type FormExit app =
  Product FormResult (Const (WidgetFor app ()))

tabulateForm ::
  (Record rec, RenderMessage app FormMessage) =>
  Tabulate rec (FormEntry app) -> -- (Field rec ~> FormEntry app)
  FormFor app (FormExit app rec)
tabulateForm = getCompose . tabulate . components form

We can automatically tabulate a FormFor app action for an entire record rec, that concatenates the Widget components and checks the FormResult in its proper fashion, just by writing a case statement on the Field rec ty what FormEntry app ty to use.

While that is neat, it still does not tell me what the glue is. Record is a type class, so as I see it, it neither falls into the HKD category nor is it essentially different from Generic approaches: Once you have your Record instance in place, you have no control over the final shape of the form produced by tabulateForm. But we’re digressing here from the OP. Instead of the recordFieldLens type class method, with HKD one could say:

data UserHKD f = User {
    _name :: f String,
    _age  :: f Int
    }
makeLenses ''UserHKD

newtype HKDLens s a = HKDLens {runHKDLens :: forall f. Lens' (s f) (f a)}

recordFieldLens :: UserHKD (HKDLens UserHKD)
recordFieldLens = User {
    _name = HKDLens name,
    _age  = HKDLens age
    } -- simple enough to be generated by TH

I expect that the tabulateRecordA can also be derived using one of the existing HKD packages, e.g. Data.Functor.Barbie.btraverse.

Indeed it does, but requires UndecidableInstances because the constraint C (f FieldOfHKD) is not smaller than C (HKD f). And yes, the standalone instance is a bit of extra boilerplate.

You mean like this record function?

Is your tabulate meant to mirror the Representable’s namesake method? You may be interested in Rank2.Distributive class which provides similar functionality for HKD records. I’ve been using it for parsing like you say.

A Record rec is kind of a like a Representable Functor, but its Rep is Field rec. I got tabulate from shortening tabulateRecord but it would not surprise me if that’s where the idea originated. The benefit of Tabulate is the ability to separate the underlying data from the functor, emulating some parts of HKDs without sacrificing automatic deriving. A challenge for Record would be to create another associated datatype, essentially the “representation of the representation”: a plain, non-GADT sum type for the fields of a record, so that we could also define type families that have different values on each field. Then Tabulate rec (SomeTypeFamily (FieldEnum rec)) could, for special type families, also change the field’s type, encompassing even more HKD features.

1 Like

Well that function seems to glue without using actual glue, that is, just uses the Semigroup s instance as far as I can tell. So the stuff between the fields must have been present around the field Formats already.

What I mean by “glue” is: The ToJSON1 instance of [] from aeson uses the ToJSON instances of the list elements, intercalates with commas and surrounds by brackets. Here, the commas and brackets are the glue. Conversely, the parser for a list uses the list element parsers but glues them with parsers for whitespace, commas and brackets. But all this is specially crafted for the list type. How would one derive this, say, from the Rep of the recursive list data definition? Its hypothetical type signature would be:

data family Glue
tabulateWithGlue :: record f -> Glue record f -> f (record Identity)

-- example
data User f = User {name :: f String, age :: f Int}
type Glue User f = UserGlue {
    glueHeader    :: f (),
    glueTitleName :: f (),
    glueSeparator :: f (),
    glueTitleAge  :: f (),
    glueFooter    :: f ()
    }

You see that the number of glue fields is not directly correlated to the number of fields in the record, but rather to the number of fields plus the syntax surrounding them. Such a record would enable the user to exercise fine control over the tabulated result, be it a serialized value or an input form.

Nothing stops you from adding the glue to the field parsers. See for example the URI format definition:

uriReference = record UriReference{
   scheme = optional (uriScheme <* literal ":"),
   authority = optional (literal "//" *> uriAuthority),
   path = encodedCharSequence pathChar `sepBy` literal "/",
   query = optional (literal "?" *> encodedCharSequence queryChar),
   fragment = optional (literal "#" *> encodedCharSequence fragmentChar)
   }

The literals are exactly the glue.

This quite arbitrarily adds the glue to some adjacent field. I’ve written many parsers like that, but it is not principled. What if you need to import/export a different format that shares the fields but the glue is different? No code re-use. Think Yaml vs. Json, CSV separators, CRLF versus Newline, …

Not quite arbitrarily in this case, the delimiters are specified in RFCs. I see your point in general. If reuse was a concern in this case, I’d probably split the above definition in two as follows:

uriReference = record (uriGlue Rank2.<*> uriFields)
uriFields = UriReference{
   scheme = specOptional uriScheme,
   authority = specOptional uriAuthority,
   path = encodedCharSequence pathChar `sepBy` literal "/",
   query = specOptional $ encodedCharSequence queryChar,
   fragment = specOptional $ encodedCharSequence fragmentChar
   }
uriGlue = UriReference{
   scheme = glueOptional (<* literal ":"),
   authority = glueOptional (literal "//" *>),
   path = Rank2.Arrow id,
   query = glueOptional (literal "?" *>),
   fragment = glueOptional (literal "#" *>)
   }

I think the spec reads pretty well, even if the two helper functions are a bit ugly to define:

specOptional :: Format Parser Maybe t x -> Format Parser Maybe t (Maybe x)
glueOptional :: Monoid t
             => (Format Parser Maybe t (Maybe x) -> Format Parser Maybe t (Maybe x))
             -> (Format Parser Maybe t Rank2.~> Format Parser Maybe t) (Maybe x)
specOptional = mapValue Just fromJust
glueOptional f = Rank2.Arrow $ \x-> mapValue join Just $ optional (f x)

That’s the kind of glue that I was after. However, you’re still limited to having one bit of glue per field. Unlikely that this scales to more complicated and less linear data structures. In particular, for your example you had to resort to id as the glue and leave some literals in the path field.
My point is that the glue is in general not a property of an individual field, but of the field being adjacent to another field or the first/last field in the record. Speaking in terms of Generics, the glue is to be added on the :*: and Meta type constructors, not the Rec1 and K1 constructors.

I like higher kinded data. I use it (well, a close pattern) in strongweak, where it allows me to conveniently define a “strong” and “weak” version of a data type at the same time, and derive generic transformations between them:

data A (s :: Strength) = A
  { a1 :: SW s Word8
  , a2 :: String }

(Lo, upon checking mid-thread, rhendric has posted a similar pattern!)

This necessitates extra boilerplate, because now you can’t derive stock X due to the SW type family. for most X. You need to write standalone derivations instead, like deriving stock instance Show A 'Strong. It’s a very minor ergonomics issue, because if you were to write this any other way via two separate definitions, you’d need to do the same anyway.

I’ve used barbies briefly, but every time so far I’ve found I was misusing it and would’ve been better off simplifying my code. For me, HKDs are the same “use with caution” bucket as promoted data constructors-- which when I learned for the first time I promptly inserted everywhere and made a big mess. Now I’ve learned to respect them and use them properly.

2 Likes