[ghc-steering-committee] Record dot notation

Cale Gibbard cgibbard at gmail.com
Wed Feb 12 22:53:11 UTC 2020


I'm writing a longer comment reiterating the stuff I posted on this
thread for the GitHub, thanks for pointing that discussion out Simon,
I'd forgotten it was a thing that would naturally exist.

It may be worth pointing out that we already have special syntax to
help with using HasField, in the form of the OverloadedLabels. You can
already do this to enable #lbl r as an alternative to getField @"lbl"
r or any number of other permutations thereof if you'd prefer
something slightly different:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}

import GHC.Records
import GHC.OverloadedLabels (IsLabel(..))
import GHC.TypeLits (Symbol)

instance forall x r a. HasField x r a => IsLabel x (r -> a) where
  fromLabel r = getField @x r

On Wed, 12 Feb 2020 at 16:39, Joachim Breitner <mail at joachim-breitner.de> wrote:
>
> Hi Cale,
>
> thanks for making sure the discussion isn’t just about whitespace, but
> also whether we want this at all!
>
> Am Dienstag, den 11.02.2020, 12:28 -0500 schrieb Cale Gibbard:
> > Since I seem to be of the opinion that this wouldn't be a good
> > inclusion while most everyone else is more convinced that *something*
> > along these lines is needed or desirable
>
> My assumption here is that to some people, the lack for nice record
> access syntax is a big pain, else they would not bother with a proposal
> like this. In most of my Haskell programming, my own pain level wasn't
> too high (although prefixed field names are a bit ugly). I had one
> rather special case where I wish I could use Haskell as an “exectuable
> specification pseudocode langauge”, and the lack of nice record syntax
> killed that idea. This proposal might have helped some here (but only
> some, not all).
>
> So I can’t really refute your point that this might not be needed.
>
>
> You bring up some points about whether this doesn't go far enough (row
> polymorphism etc.). But this proposal really only add syntax for an
> existing feature (HasField), so maybe this is not the right place for a
> semantic critique of HasField? Of course it is a valid point to say
> that HasField is a feature that is not “good enough” to deserve a slice
> of the precious “.” operator.
>
>
> > And if this is not about the concrete syntax of using dot
> > for yet another thing, then what is it about? We presumably already
> > have reasonably convenient ways of expressing everything here, don't
> > we?
>
> I guess to some it isn't reasonable to write `f (getField @"lbl" r)`…?
>
> Cheers,
> Joachim
> --
> Joachim Breitner
>   mail at joachim-breitner.de
>   http://www.joachim-breitner.de/
>
>
> _______________________________________________
> ghc-steering-committee mailing list
> ghc-steering-committee at haskell.org
> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee


More information about the ghc-steering-committee mailing list