GHC support for the new "record" package

Adam Gundry adam at well-typed.com
Mon Jan 26 09:20:25 UTC 2015


Thanks, Simon, I think we're starting to find a nice story indeed. Your
implicit values idea is what I was starting to grope towards with
IsRecordField, but I hadn't spotted the similarity to implicit parameters.

Like Neil, I still think it's worth separating the magically-solved
typeclass that describes when a field belongs to a record (aka HasField)
from the typeclass that explains how to interpret the #x syntax (aka
IsRecordField/IV). In particular, with your plan the composition of two
implicit values ends up having an ambiguous type:

  #foo . #bar :: (IV "foo" (b -> c), IV "bar" (a -> b)) => a -> c

We need to be able to express that the codomain is functionally
dependent on the domain (or vice versa, for van Laarhoven lenses), which
I think entails having some

  instance ... => IV n (r -> a).

Moreover, seeing as we're so close, it would be nice if we come out of
this with a way to get lenses "for free" from fields, rather than
needing TH.

All this brings us back to the question of which instance(s) to have for
(->), if any. I think Neil's suggestion for avoiding orphans is
feasible... in fact, I believe the only real conflict is between

  instance IV n (r          -> a       )
  instance IV n ((a -> f b) -> s -> f t)

so we could probably just have two extensions to fix an additional
parameter at one of two values. Although I'm not keen on the aesthetics.
Perhaps we should just vote on whether preferential treatment is given
to selectors or lenses, and pick one?

Adam


On 24/01/15 07:45, Neil Mitchell wrote:
> Hi All,
> 
> I fixed a missing "x" in one of the instances. I like the proposal,
> mostly because it has nothing to do with records, leaving people to
> experiment with records in libraries.
> 
> I'm not keen on the use of Template Haskell to define lenses, and the
> fact that all base libraries are going to need custom makeLens
> definitions set apart from their definitions, plus IV is rather
> "wired" into record selectors, which can't be undone later. I think we
> can fix some of that by desugaring record definitions to:
> 
> data T = MkT {x :: Int}
> 
> instance FieldSelector "T" T Int where
>      fieldSelector (MkT x) = x
> 
> Then someone can, in a library, define:
> 
> instance FieldSelector x r a => IV x (r -> a) where
>      iv = fieldSelector
> 
> Now that records don't mention IV, we are free to provide lots of
> different instances, each capturing some properties of each field,
> without committing to any one style of lens at this point. Therefore,
> we could have record desugaring also produce:
> 
> instance FieldSetter "T" T Int where
>     fieldSet v (T _) = T v
> 
> And also:
> 
> instance FieldSTAB "T" T Int where
>     fieldSTAB = ... the stab lens ...
> 
> (As we find new interesting types of operations over a field, with
> different levels of polymorphism etc, we can keep adding new ones
> without breaking compatibility, and most users won't care. Prototyping
> new ones in Template Haskell is still probably a good idea.) Now
> someone can define, in a record library:
> 
> instance (FieldSelector x r a, FieldSetter x r a) => IV x (Lens r a) where
>     iv = makeLens fieldSelector fieldSet
> 
> Or, for people who want #x to be a STAB lens directly (without a Lens
> type wrapper), they can omit the IV x (r -> a) instance, and only have
> #x have instances producing the STAB lens.
> 
> The one downside of this plan is orphan instances, which means if you
> are writing a library and use one type of IV declaration (the selector
> one), then anyone else building on your library won't be able to use a
> different type of IV (the stab one). One potential way to fix that is
> to parameterise IV, so you can say (warning, even more half-baked
> thoughts ahead):
> 
> {-# LANGUAGE ImplicitValues=MyType #-}
> 
> Where MyType is a type I've defined in one of my imports, and then
> desugar #x to:
> 
> iv @ "x" @ MyType @ alpha
> 
> And extend IV with an extra type parameter. Now all the Lens library
> IV instances can include LensType, and people can mix and match
> different record schemes in different modules.
> 
> Separately, the pattern: data T = ...; $(makeLens 'T) crops up a lot,
> and is gently ugly. I wonder if there should be an extension that
> let's you write: data T = ... deriving ('makeLens), or even just
> deriving (Lens) which desugars to the same thing?
> 
> Thanks, Neil



-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


More information about the ghc-devs mailing list