GHC support for the new "record" package

Edward Kmett ekmett at gmail.com
Wed Jan 28 23:40:58 UTC 2015


There is a problem with the old TRex syntax.

In a world with kind signatures and rank-2 types, it would appear that

    type Point2D = Rec ( x :: Coord, y :: Coord)

is ambiguous.

Is Coord a kind signature being applied to x and y which are type variables
brought into scope implicitly as

   type Point2D = forall (x :: Coord, y :: Coord) => Rec (x, y)

would make more explicit?

e.g.

type Lens s t a b = Functor f => (a -> f b) -> s -> f t
works today in ghc, even though f isn't explicitly scoped and elaborates to:

type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t

-Edward

On Wed, Jan 28, 2015 at 4:48 PM, Nikita Volkov <nikita.y.volkov at mail.ru>
wrote:

> Chris, this is great! Looks like we can even get rid of the Rec prefix!
>
>    -
>
>    A phrase in round braces and with :: is itself unambiguous in the type
>    context.
>     -
>
>    A phrase in round braces with = symbols is unambiguous in the
>    expression context.
>
> Concerning the pattern context a solution needs to be found though. But
> the two points above are enough for me to fall in love with this direction!
> The {| braces had a too icky of a touch to them and the plain { required
> the user to choose whether to use the standard record syntax or anonymous
> one on the module scale, but not both.
>>
>
> 2015-01-29 0:26 GMT+03:00 Christopher Done <chrisdone at gmail.com>:
>
>> There’s too much to absorb in this discussion at the moment and I’m
>> late to the party anyway, but I would like to make a small note on
>> syntax. Given that this is very similar to TRex both in behaviour and
>> syntactic means of construction, why not just take TRex’s actual
>> syntax? http://en.wikipedia.org/wiki/Hugs#Extensible_records
>>
>> type Point2D = Rec (x::Coord, y::Coord)
>> point2D = (x=1, y=1) :: Point2D
>> (#x point)
>>
>> It seems like it wouldn’t create any syntactical ambiguities (which is
>> probably why the Hugs developers chose it).
>>
>> Ciao
>>
>> On 20 January 2015 at 22:44, Simon Marlow <marlowsd at gmail.com> wrote:
>> > For those who haven't seen this, Nikita Volkov proposed a new approach
>> to
>> > anonymous records, which can be found in the "record" package on
>> Hackage:
>> > http://hackage.haskell.org/package/record
>> >
>> > It had a *lot* of attention on Reddit:
>> > http://nikita-volkov.github.io/record/
>> >
>> > Now, the solution is very nice and lightweight, but because it is
>> > implemented outside GHC it relies on quasi-quotation (amazing that it
>> can be
>> > done at all!).  It has some limitations because it needs to parse
>> Haskell
>> > syntax, and Haskell is big.  So we could make this a lot smoother, both
>> for
>> > the implementation and the user, by directly supporting anonymous record
>> > syntax in GHC.  Obviously we'd have to move the library code into base
>> too.
>> >
>> > This message is by way of kicking off the discussion, since nobody else
>> > seems to have done so yet.  Can we agree that this is the right thing
>> and
>> > should be directly supported by GHC?  At this point we'd be aiming for
>> 7.12.
>> >
>> > Who is interested in working on this?  Nikita?
>> >
>> > There are various design decisions to think about.  For example, when
>> the
>> > quasi-quote brackets are removed, the syntax will conflict with the
>> existing
>> > record syntax.  The syntax ends up being similar to Simon's 2003
>> proposal
>> >
>> http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html
>> > (there are major differences though, notably the use of lenses for
>> selection
>> > and update).
>> >
>> > I created a template wiki page:
>> > https://ghc.haskell.org/trac/ghc/wiki/Records/Volkov
>> >
>> > Cheers,
>> > Simon
>> > _______________________________________________
>> > ghc-devs mailing list
>> > ghc-devs at haskell.org
>> > http://www.haskell.org/mailman/listinfo/ghc-devs
>>
>
>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://www.haskell.org/mailman/listinfo/ghc-devs
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20150128/78a11ef7/attachment.html>


More information about the ghc-devs mailing list