About type sharing (mostly) and records (desugaring, mostly)

Hi,
After re-reading the very good Well Typed blog post type level sharing now, I have been wondering a number of things.

  • Why can’t we have the same logic for type sharing as we have for value sharing in any pre-core generation phase of GHC. It is my understanding that GHC performs opportunistic Common Subexpression Elimination and then I don’t see what’s particularly specific at the type level here.

    Now assuming nothing inherent prevents the above, let’s see my naive idea in practice :

apBaseline :: Applicative f => (A -> B -> C -> r) -> f r
apBaseline f =
                          (pure f)
    <*> @A @(B -> C -> r) (pure A)
    <*> @B @(     C -> r) (pure B)
    <*> @C @(          r) (pure C)
-- would trigger some common sub expression simplification to something like by a mere  :

type X =  C -> r
apBaseline :: Applicative f => (A -> B -> C -> r) -> f r
apBaseline f =
                     (pure f)
    <*> @A @(B -> X) (pure A)
    <*> @B @(     X) (pure B)
    <*> @C @(     r) (pure C)

And


hlistBaseline :: HList '[A, B, C, D]
hlistBaseline =
      HCons @'[A, B, C, D] A
    $ HCons @'[   B, C, D] B
    $ HCons @'[      C, D] C
    $ HCons @'[      D] D
    $ HNil

-- Or something even more systematic, in N pass where N is the number of rewrite until we don't find any common expression n the types anymore.

type X1 =  C : D
type X2 =  B : X1
hlistBaseline :: HList '[A, B, C, D]
hlistBaseline =
      HCons @'[A, X2] A
    $ HCons @'[   X2] B
    $ HCons @'[      X1] C
    $ HCons @'[      D] D
    $ HNil

Now having N rewrites for every files is perhpas not very realistic in termes of compilation, but then why don’t we do this at desugaring ? I mean at some point we have to generate those quadratic core type applications, so we have them at hand and could potentially reduce them before writing them.

  • The blog post mention a paper about omitting some type applications in core altogether. As someone whose not very familiar with core, this certainly seems like a huge improvement. The paper says that system IF was implemented in GHC, but it didn’t result in better compile times (even though re ducing 80% of type applications). It says the core rewriting rules (such as above but better) are costly. Then why don’t we desugar directly without TA using those rules ? Or maybe only targeting the “obviously” non linear cases.

  • The trick of using existential type to avoid generating selectors on records while very clever seems odd. Why doesn’t the XNoFieldSelectors extension prevent them from beeing genereated altogether ?

  • I’ve read somewhere (probably on a Well Typed blog post) that records also have this issue of quadratic core size, but then how are records desugared (I remember something about nested tuples, but can’t find the reference) ? And can anyone eli5 what are the cause for quadratic behaviors in this case ?
    As edsko mentioned in the thread announcing large-anon/large-record libraries, “selector functions are only one of many, many reasons why traditional records lead to quadratic code and compilation times”, but is there a list ? Or perhaps the best course of action is to simply design a new record system on the side, not to bother GHC devs with anything ?

So the reason I’m interested in all this, is mainly anonymous/extensible records and the lack of implementation directly backed in the compiler. The state of records in haskell has only very very partially improved for the past 10 years (with the notable exception of the the large-x libraries from well-typed, but then these are still not in ghc), and I’d like to get a better understanding of why (at least to grasp the general blockers, if any, excluding people’s lack of time).

thanks

3 Likes

So I had missed an important source of information about sharing :

TL;DR is, my naive idea is approximately what’s described in the ticket and doing it in the desugarer is even mentioned.
My question about how records desugar to core still holds though…

1 Like

About records in Haskell - from a quick search on this Discourse, using the term Haskell records:

…does any of that help?

1 Like

It certainly helps on giving context and explanations about the somewhat crazy inertia to overcome the status quo, but I don’t find anything about the technicalities of the current record system (in particular: how they desugar, and why the necessity to keep the selectors function generated no matter what). Perhaps I havn’t looked enough though ?

…well, do-notation is also a syntactic additive, and the Haskell 2010 Report seems to describe that reasonably well - what does it say about “record notation” ? Searching for record:

…continuing the search, but for record syntax:

From that I would reasonably assume record syntax simplifies down to a combination of regular constructors and generated selector functions. That in turn seems to also explain the need to keep said selectors. But I would also check the GHC sources to verify both assumptions…

1 Like

Hi, As the initiator of that thread … it isn’t talking about Haskell’s/GHC’s record so-called system at all. It’s asking why Haskell never implemented something worthy of the name ‘record system’. SML’s record system is nothing like Haskell’s, as soon as you start looking under the hood.

Because you’re likely to export this data type; and the importing module might not have the fancy-pants overloaded record access switched on. So now it needs those selector functions. (Don’t shoot the messenger: I’m passing on the justification used at the time. No module nowhere “needs” selector functions: you can always use pattern matching. IMO)

1 Like

So, I didn’t think of this before but ghc can give me an example quite easily so a fairly simple module such as this :


data Test = Test {
  fieldA :: Int,
  fieldB :: Double,
  fieldC :: [Int]
}

data TestMore = TestMore {
  fieldD :: Test,
  fieldE :: [Test]
}

desugars to this

[1 of 1] Compiling MyModule.Ok      ( src/MyModule/Ok.hs, src/MyModule/Ok.o )

==================== Tidy Core ====================
Result size of Tidy Core
  = {terms: 148, types: 80, coercions: 0, joins: 0/0}

-- RHS size: {terms: 5, types: 6, coercions: 0, joins: 0/0}
fieldC :: Test -> [Int]
[GblId[[RecSel]], Arity=1, Unf=OtherCon []]
fieldC
  = \ (ds_dvd :: Test) ->
      case ds_dvd of { Test ds1_dve ds2_dvf ds3_dvg -> ds3_dvg }

-- RHS size: {terms: 5, types: 6, coercions: 0, joins: 0/0}
fieldB :: Test -> Double
[GblId[[RecSel]], Arity=1, Unf=OtherCon []]
fieldB
  = \ (ds_dv9 :: Test) ->
      case ds_dv9 of { Test ds1_dva ds2_dvb ds3_dvc -> ds2_dvb }

-- RHS size: {terms: 5, types: 6, coercions: 0, joins: 0/0}
fieldA :: Test -> Int
[GblId[[RecSel]], Arity=1, Unf=OtherCon []]
fieldA
  = \ (ds_dv5 :: Test) ->
      case ds_dv5 of { Test ds1_dv6 ds2_dv7 ds3_dv8 -> ds1_dv6 }

-- RHS size: {terms: 5, types: 5, coercions: 0, joins: 0/0}
fieldE :: TestMore -> [Test]
[GblId[[RecSel]], Arity=1, Unf=OtherCon []]
fieldE
  = \ (ds_dv2 :: TestMore) ->
      case ds_dv2 of { TestMore ds1_dv3 ds2_dv4 -> ds2_dv4 }

-- RHS size: {terms: 5, types: 5, coercions: 0, joins: 0/0}
fieldD :: TestMore -> Test
[GblId[[RecSel]], Arity=1, Unf=OtherCon []]
fieldD
  = \ (ds_duZ :: TestMore) ->
      case ds_duZ of { TestMore ds1_dv0 ds2_dv1 -> ds1_dv0 }

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$trModule1_ruL :: GHC.Prim.Addr#
[GblId, Unf=OtherCon []]
$trModule1_ruL = "main"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$trModule2_rvv :: GHC.Types.TrName
[GblId, Unf=OtherCon []]
$trModule2_rvv = GHC.Types.TrNameS $trModule1_ruL

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$trModule3_rvw :: GHC.Prim.Addr#
[GblId, Unf=OtherCon []]
$trModule3_rvw = "MyModule.Ok"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$trModule4_rvx :: GHC.Types.TrName
[GblId, Unf=OtherCon []]
$trModule4_rvx = GHC.Types.TrNameS $trModule3_rvw

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
MyModule.Ok.$trModule :: GHC.Types.Module
[GblId, Unf=OtherCon []]
MyModule.Ok.$trModule
  = GHC.Types.Module $trModule2_rvv $trModule4_rvx

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep_rvy :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep_rvy
  = GHC.Types.KindRepTyConApp
      GHC.Types.$tcDouble (GHC.Types.[] @GHC.Types.KindRep)

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep1_rvz :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep1_rvz
  = GHC.Types.KindRepTyConApp
      GHC.Types.$tcInt (GHC.Types.[] @GHC.Types.KindRep)

-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
$krep2_rvA :: [GHC.Types.KindRep]
[GblId, Unf=OtherCon []]
$krep2_rvA
  = GHC.Types.:
      @GHC.Types.KindRep $krep1_rvz (GHC.Types.[] @GHC.Types.KindRep)

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep3_rvB :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep3_rvB = GHC.Types.KindRepTyConApp GHC.Types.$tc[] $krep2_rvA

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tcTest1_rvC :: GHC.Prim.Addr#
[GblId, Unf=OtherCon []]
$tcTest1_rvC = "Test"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tcTest2_rvD :: GHC.Types.TrName
[GblId, Unf=OtherCon []]
$tcTest2_rvD = GHC.Types.TrNameS $tcTest1_rvC

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
MyModule.Ok.$tcTest :: GHC.Types.TyCon
[GblId, Unf=OtherCon []]
MyModule.Ok.$tcTest
  = GHC.Types.TyCon
      4959299669405483955##
      12816139518062252538##
      MyModule.Ok.$trModule
      $tcTest2_rvD
      0#
      GHC.Types.krep$*

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep4_rvE :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep4_rvE
  = GHC.Types.KindRepTyConApp
      MyModule.Ok.$tcTest (GHC.Types.[] @GHC.Types.KindRep)

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep5_rvF :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep5_rvF = GHC.Types.KindRepFun $krep3_rvB $krep4_rvE

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep6_rvG :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep6_rvG = GHC.Types.KindRepFun $krep_rvy $krep5_rvF

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep7_rvH :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep7_rvH = GHC.Types.KindRepFun $krep1_rvz $krep6_rvG

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'Test1_rvI :: GHC.Prim.Addr#
[GblId, Unf=OtherCon []]
$tc'Test1_rvI = "'Test"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'Test2_rvJ :: GHC.Types.TrName
[GblId, Unf=OtherCon []]
$tc'Test2_rvJ = GHC.Types.TrNameS $tc'Test1_rvI

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
MyModule.Ok.$tc'Test :: GHC.Types.TyCon
[GblId, Unf=OtherCon []]
MyModule.Ok.$tc'Test
  = GHC.Types.TyCon
      9856255924558680085##
      11575134686824913712##
      MyModule.Ok.$trModule
      $tc'Test2_rvJ
      0#
      $krep7_rvH

-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
$krep8_rvK :: [GHC.Types.KindRep]
[GblId, Unf=OtherCon []]
$krep8_rvK
  = GHC.Types.:
      @GHC.Types.KindRep $krep4_rvE (GHC.Types.[] @GHC.Types.KindRep)

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep9_rvL :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep9_rvL = GHC.Types.KindRepTyConApp GHC.Types.$tc[] $krep8_rvK

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tcTestMore1_rvM :: GHC.Prim.Addr#
[GblId, Unf=OtherCon []]
$tcTestMore1_rvM = "TestMore"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tcTestMore2_rvN :: GHC.Types.TrName
[GblId, Unf=OtherCon []]
$tcTestMore2_rvN = GHC.Types.TrNameS $tcTestMore1_rvM

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
MyModule.Ok.$tcTestMore :: GHC.Types.TyCon
[GblId, Unf=OtherCon []]
MyModule.Ok.$tcTestMore
  = GHC.Types.TyCon
      8510355829756615054##
      17370134490921635344##
      MyModule.Ok.$trModule
      $tcTestMore2_rvN
      0#
      GHC.Types.krep$*

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep10_rvO :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep10_rvO
  = GHC.Types.KindRepTyConApp
      MyModule.Ok.$tcTestMore (GHC.Types.[] @GHC.Types.KindRep)

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep11_rvP :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep11_rvP = GHC.Types.KindRepFun $krep9_rvL $krep10_rvO

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep12_rvQ :: GHC.Types.KindRep
[GblId, Unf=OtherCon []]
$krep12_rvQ = GHC.Types.KindRepFun $krep4_rvE $krep11_rvP

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'TestMore1_rvR :: GHC.Prim.Addr#
[GblId, Unf=OtherCon []]
$tc'TestMore1_rvR = "'TestMore"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'TestMore2_rvS :: GHC.Types.TrName
[GblId, Unf=OtherCon []]
$tc'TestMore2_rvS = GHC.Types.TrNameS $tc'TestMore1_rvR

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
MyModule.Ok.$tc'TestMore :: GHC.Types.TyCon
[GblId, Unf=OtherCon []]
MyModule.Ok.$tc'TestMore
  = GHC.Types.TyCon
      3029184788634965850##
      12315380093137452644##
      MyModule.Ok.$trModule
      $tc'TestMore2_rvS
      0#
      $krep12_rvQ

I’ll take a deeper look at this later, but it’s not immediatly obvious to me why the generated core is quadratic in the number of fields from either the explanations in ghc or all the reading from prior sources. That’s my “ultimate” question which hasn’t been answered so far, but I suspect I can find out by myself, eventually.

I’m not qualified to comment on the bulk of your post but … So-called anonymous/extensible records are not merely something a little way beyond current record features; they need an utterly different semantics. Furthermore the key feature of the ‘anonymous’ is to actively prevent access by position; whereas H98 named field access is merely syntactic sugar for positional.

For comparison, purescript’s design for records has just thrown away H98 and started again; you’re not allowed positional access. (But purescript doesn’t support extensible/merging records by named field.)

AFAICT (and I’ve asked this question several times several ways round, never got any sort of an answer), Haskell’s type theory (System F+#~ or whatever it’s got to these days) is not adequate to support typing for anonymous/extensible records.

Contrast that for Lenses you need to supply a load of boilerplate code (typically via Template Haskell) in effect translating each lens into positional access for each data type.

As I said on that discourse thread @atravers linked to (thank you), Haskell had the opportunity ~2000 to do something better than H98’s stopgap design for records. There was a swirl of discussion but nothing happened. Nowadays there’s such a bulk of legacy code using H98 style, I guess we’re stuck with it.

It turns out to be not too hard to build more flexible extensibility on top of Hugs’ system TRex. But I suspect there’s no way to translate its semantics into System F-whatever. (There’s a fair amount of ad-hocery inside the Hugs compiler.) Frankly, the type theorists have exhausted my patience: all this fancy abstract whatever and they can’t describe a records system with the power of even grotty SQL.

If anonymous/extensible records are a priority for you, find some other language than Haskell.

1 Like

…and “quadratic field complexity” of record syntax isn’t mentioned in the Report: perhaps said complexity is in regards to those GHC extensions.

Damn, that’s depressing. Haskell is good in many areas so I guess I’ll keep going. On the other hand, without anonymous records, I’m forced to use ugly workarounds with “so-called” safe undefined protected by fancy type machinery. Or complex type families constructs to simulate “subtypes” of a type (i.e. switch on or off fields through a Maybe Void or () type). This is verbose and unnecessary. But then I only have very limited time to offer and the areas in which haskell needs help are numerous and growing so… Maybe i’ll end up considering your suggestion, time will tell.

PS: it seems large-anon is doing a great job at filling my needs for now though, after a few experiments I find it very impressive. I’m a bit wary of having to rewrite huge chunks of code when ghc gets a baked in implementation

You could also charge ahead and use your struggles and learning to contribute upstream! GHC evolves and evolves and evolves.

1 Like

GHC has decided to put all its efforts into Dependent Haskell. Having done that, they’re discovering DH needs a great deal more headscratching than Eisenberg’s thesis would suggest. So they’ve delivered … approximately nothing. AFAICT DH won’t help one jot with an anonymous/extensible record design.

Then I don’t think you’ll be faced with rewriting anything for at least ten years. If GHC evolves, it’s so glacial, I’m failing to notice. (Written bitterly by someone who was specifically invited to spec up amendments for a better-principled FunDeps/overlap to support an anonymous/extensible records system – which I was reluctant to do because I expected the effort to be pointless – and … I didn’t even get the courtesy of an acknowledgment.)

Well, you’re in good company:

  • twenty years ago, Robert Ennal’s research into optimistic evaluation looked like it was “going mainstream”…but it didn’t: presumably the promising initial results from his prototype didn’t carry through to production.

  • More recently, Peng Li’s research into lightweight concurrency, while being integrated into Lighthouse (derived from the House OS), could never quite match the performance of the current approach GHC uses: after years of being kept in sync with the regular one, that particular branch has also been abandoned.

Perhaps it’s due to the limits of the dial-up Internet connection I was using in 2003, but I don’t recall Ennals making much of a hullabaloo about his work going nowhere: he just went elsewhere! As for Li, I vaguely remember some unhappiness being expressed somewhere (I could be wrong), but he moved on as well.

They both had invested much more time and effort into their respective research, so I would have thought they would have far more to complain about…but apparently they have chosen to now remain quiet. Why they have made that choice is a question I have no answer to: feel free to ask!

Your repeated grudge against DH in this forum is noticeable to many newbies including me already. Perhaps you could rephrase it to something constructive that we could do something about in another post, instead of poisoning this thread?

1 Like

The large-anon guys are saying that the core generated for HasField instances are quadratic. (Also for instances over type-level lists – which derive ultimately from the HList 2004 work.) HasField is not H98; type-level lists are not H98; HList relied on beyond-H98 features like overlapping instances and FunDeps. So I wouldn’t expect H98-compliant code to suffer the quadratic explosion, hence why it’s not “mentioned in the Report”.

To conform with H98, each field name gets declared only once; so each accessor function is accessing only one record type. So (maybe I’m being too naieve) I’d expect code size to be linear in the number of fields ceteris paribus (as we Economists like to say).

And your sample code hasn’t declared any instances at all – not even ... deriving (Eq, Show). So I don’t think it’s going anywhere near what large-anon is talking about.

OTOH you don’t say what extensions you switched on. So perhaps the code is using beyond-H98 features and they have generated ‘secret’ instances? (And sorry, I can’t read that desugarring, but are you saying the code is quadratic?)

So do we suffer quadratic explosion with extensible/anonymous records? I’m asking/I don’t know. Of course depends what choices we make for the design. I’ll take Hugs/TRex for definiteness – not because I’m claiming it’s “better” or “more suitable for Haskell” than other designs.

An anonymous record type (well ok I’m giving it a type synonym for easy mention)

type Test = Rec( fieldA :: Int, fieldB :: Double, fieldC :: [Int] )    -- is shorthand for
--  Rec( fieldA :: Int | ( fieldB :: Double | ( fieldC :: [Int] | EmptyRow ))  -- nested

type TestMore = Rec( fieldB :: [Test], fieldA :: Test)    -- not your TestMore example
--  Rec( fieldA :: Test | (fieldB :: [Test] | EmptyRow ))

-- an instance would look like (I'm omitting some implementation detail)

instance Eq EmptyRow  where ...              -- base case empty rec

instance (Eq a, Eq rest) => Eq (Rec( fieldA :: a | rest ))  where ...
instance (Eq b, Eq rest) => Eq (Rec( fieldB :: b | rest ))  where ...

So there’s one instance for each distinct field name across all possible field types. There’s no instances for all the possible combos of field names. So linear in the number of field names? I am worried (looking at what the large-anon folk are saying) with that recursive instance Eq rest =>. Because that looks like what happens with type-level lists.

Now here’s the trick with Hugs/Trex: although the types look like they’re nested, the implementation turns the record values into a ‘flat’ vector of fields. What’s more puts the field names in alphabetical order, irrespective of the order of appearance in the program source. That’s what the Rec( ) construct is doing. So this doesn’t suffer the problem with the values corresponding to a type-level list that there’s cons-like constructors all the way down. (Something else the large-anon folk are worried about.)

(meta: I hope this speculation is an example for @travers as to where I’m going/what I’m thinking about. I feel DH has nothing to say here, but please correct if I’m wrong. Oh, and it was you hooked me into this discussion by linking to one of my posts/threads.)

1 Like

I feel DH has nothing to say here, but please correct if I’m wrong.

Hrm:

So just stop the hubbub.


Oh, and it was you hooked me into this discussion by linking to one of my posts/threads.

I’ll ask the moderators if it’s possible to exclude “your posts/threads” from appearing in search results - that way, you being “hooked” into future discussions will be the result of someone seeking out that content intentionally

There is a possibility here for improvement: because they are just another notational addtitive (like do), Haskell 2010’s record syntax - with sufficient cunning - could be redefined in terms of another, more comprehensive record system:

  • Old code using record syntax continues to work as before;

  • New code can make direct use of the new record system.

Any library-backed record implementation which can provide such a redefinition must surely be a potential candidate for a new Haskell addendum (like hierarchical-module name and FFI support were).

That’s a brave claim without an actual proposal in front of us.

That’s what HasField is trying to do – and without even a “new record system”. And it’s hard to retain backwards compatibility: if a module using HasField is imported into a module that doesn’t (or vice versa); if the modules declare same-named fields. And turns out HasField gives this quadratic explosion in instances.

purescript's record decls look superficially like Haskell’s, but with incompatible semantics. Again if a future Haskell were to import a purescript style record into Haskell (or v.v) with same-named fields; the accessor’s instances must get overloaded with different semantics. Now try exporting a function with that accessor call embedded in its definition.

So Hugs.Trex uses distinct syntax for its records. (Which caused Mark Jones consternation at the time.) There’s no attempt to share anything: you can have Trex fields same-named as H98 fields, but you can’t export those Trex accessors; you can’t use the Trex accessors on H98 data structures (type mis-match).

I don’t see anybody talking about merely a library-backed anything. Everybody wants new syntax (or to repurpose existing syntax), with special magic between the syntax and object code. We might arrive at the get code being merely library calls (overloaded per record type); set/update (esp type-changing) seems a lot nastier.

I’m wondering if this talk of quadratic explosion is rather too much ‘the sky is falling’. To take the initial example:

This is generic code. (IOW I’m disagreeing with the authors that’s come from “simple Haskell code”. The original code was short; if you’re gonna write highly abstract code that’s so amorphous, expect to pay for it.) So we don’t know what instance of Functor (Applicative) we’re using; hence all those type arguments. At a usage site, apBaseline appears supplied with known types; the overloading gets resolved; the type arguments get optimised away(?)

Turning to HasField, field access must use a field name that gets taken as a ‘literal’ type-level String; the usage must appear in a context where the data type must be resolvable syntactically (from the appearance of the data constructor, or a type annotation). So there’s no generic code getting planted(?)

The ‘Well Typed’ blog post goes on to consider HList examples. And that seems less tractable, because there’s a HCons constructor all the way down the spine, each appearance at a different type. Hence (I’m not saying anything new here) HList is(/was in 2004) a neat proof-of-concept for a record-alike system; it’s not realistic for ‘industrial strength’ records.

That’s a brave claim [about record syntax…]

Then go and ask the authors of the Haskell 2010 Report about what the intended meaning of this earlier post’s quote (from page 62 of 239 of said document) should be…