Experiment: alternative typed record syntax using OverloadedRecordDot and RebindableSyntax

I am experimenting with using RebindableSyntax and OverloadedRecordDot to achieve an alternative record syntax, with nested record dot support, field name duplication error message, etc. Here is the TL;DR version:

type SocialLinks = TypedRecord
  '[ NamedField "github" String
   ]

type Person = TypedRecord
  [ NamedField "name" String
  , NamedField "age" Int
  -- , NamedField "age" Double -- duplicate field detection working
  , NamedField "friends" [Person'] -- NOTE! recursive definition of type alias not allowed
  , NamedField "social" SocialLinks
  ]
newtype Person' = MkPerson Person

main = do
  let alice = mkPerson "alice" 32 [] "alice.eth"
  let bob = mkPerson "bob" 42 [alice] "bob.sol"
  print bob
  print (MkPerson bob) -- different show instance
  print (bob.name, bob.age)
  print bob.friends
  print bob.social.github

Output:

MkNamedField "bob" :* (MkNamedField 42 :* (MkNamedField [name: alice, age: 32, friends: [], social: MkNamedField "alice.eth" :* Nil] :* (MkNamedField (MkNamedField "bob.sol" :* Nil) :* Nil)))
name: bob, age: 42, friends: ["alice"], social: MkNamedField "bob.sol" :* Nil
("bob",42)
[name: alice, age: 32, friends: [], social: MkNamedField "alice.eth" :* Nil]
"bob.sol"

I want to use it in the eDSL I am building, since the default record syntax won’t suffice for the eDSL. I would like to hear some feedback, too, before I go further with this approach.

Full code is available at:

2 Likes

I also need something like it for my eDSL, for now, I settled on this (here in action):

type (:=) :: Symbol -> Type -> Type
data label := ty = (KnownSymbol label) => Proxy label := ty

newtype Row (types :: [Type]) = Row [Any]

instance HasField l (Row ((l := t) : e)) t where
    getField (Row xs) = unsafeCoerce $ xs !! 0
    {-# INLINE getField #-}

instance HasField l (Row (_0 : (l := t) : e)) t where
    getField (Row xs) = unsafeCoerce $ xs !! 1
    {-# INLINE getField #-}

instance HasField l (Row (_0 : _1 : (l := t) : e)) t where
    getField (Row xs) = unsafeCoerce $ xs !! 2
    {-# INLINE getField #-}

instance HasField l (Row (_0 : _1 : _2 : (l := t) : e)) t where
    getField (Row xs) = unsafeCoerce $ xs !! 3
    {-# INLINE getField #-}

Which is pretty similar, although I have to note that I want it to be backed by something faster than a linked list in the future (which is why I don’t mind it being unsafe under the hood).

The big difference is that I have a field name duplication error message for “free”, by GHC rejecting such code with overlapping instances error. Sadly, it is rejected at a usage site, and the error is not domain specific. Another tradeoff is that I can only provide n HasField instances (but I plan to alleviate that by providing some TH function that could derive more, if needed). Providing other instances might also not be pretty.

I do avoid TypeFamilies though, which I keep reading is a good thing. It makes me wonder which approach compiles faster.

That being said, I don’t really know if this is the way. It seems to work for my use case, and more importantly, the interface is just OverloadedRecordDot and opaque type with a type list, so quite abstract.

One question I have is what RebindableSyntax is needed for? Your code seems to work fine for me with that extension removed.

1 Like

Indeed. The rebindablesyntax was meant to be about setField, but I haven’t finished that part of the experiment.

Good to hear that you are also trying similar thing.

1 Like

Naive approach to a custom record syntax and/or anonymous records will have horrible compile time performance, see Avoiding quadratic core code size with large records - Well-Typed: The Haskell Consultants and #20264: let-bind more types to save space · Issues · Glasgow Haskell Compiler / GHC · GitLab.

Apparently the solution is to use the large-anon library (see large-anon: Practical scalable anonymous records for Haskell - Well-Typed: The Haskell Consultants for the overview) which has been carefully crafted to avoid this problem.

5 Likes