[Haskell-cafe] Shadowing record field names

Tikhon Jelvis tikhon at jelv.is
Sat Dec 23 19:47:22 UTC 2017


This is a real pain point with records in Haskell.

The fundamental problem is that unlike most languages with records or
object, field names are treated as normal identifiers in Haskell. Other
languages make fields special—you can only use them with the . operator or
in other select contexts. The advantage is that you can do things like
`a.author == author`; the disadvantage is that fields become a second-class
citizen.

At work, we have a solution that's really nice to use built on top of
DuplicateRecordFields and OverloadedLabels. Our approach follows the ideas
in the OverloadedRecordFields proposal but with a lens flavor—very similar
to the overloaded-records[1] package. (We don't use that package directly
because I wrote our own version before I knew about it and I like the
ergonomics of our internal version a bit more.)

We have a couple of typeclasses for reading and writing fields:

class HasField (field :: Symbol) s a | s -> a where
  getField :: s -> a

class UpdatesField (field :: Symbol) s t b | name t -> b, name s b -> t
where
  updateField :: s -> b -> t

A record field can be both read and updated:

type Field field s t a b = (HasField field s a, UpdatesField field name s t
b)

field :: forall (name :: Symbol) s t a b. Field name s t a b => Lens s t a b
field = lens (getField @name) (updateField @name)

Then we have some Template Haskell for generating instances of these
classes. Here's a contrived example:

data Foo a = Foo { bar :: [a] }

record ''Foo

which generates:

instance HasField "bar" (Foo a) a where
  getField = bar

instance UpdatesField "bar" (Foo a) (Foo b) b where
  updateField foo bar' = foo { bar = bar' }

Given these, we can already write code looking up fields as lenses:

> Foo [1,2,3] ^. field @"bar"
[1,2,3]

Now fields aren't normal identifiers any more, the names can be shared over
different records (with DuplicateRecordFields) and you can write functions
polymorphic over any record with a given field.

The names and details here are a bit different, but I believe this is
otherwise exactly what overloaded-records gives you. You could also replace
the TH to generate instances with generics in the style of the generic-lens
library.

However, the field @"bar" is painfully verbose. We solve this using
OverloadedLabels and a somewhat shady orphan instance for IsLabel:

instance (Functor f, Field name s t a b, a' ~ (a -> f b), b' ~ (s -> f t))
=> IsLabel name (a' -> b') where
  fromLabel = field @name

The details are a bit fiddly, but this is what we need to make type
inference work correctly. This lets us replace field @"name" with #name:

> Foo [1,2,3] ^. #bar
[1,2,3]
> Foo [1,2,3] & #bar . each %~ show
Foo { bar = ["1","2","3"] }

The downside is that this is an orphan instance for IsLabel for *all
functions*. You would not want to use this in a library but it's fine in an
executable as long as you don't mind potentially needing to reword things
if a similar IsLabel instance is added to base. (A risk I'm willing to take
for better syntax :))

Apart from that (somewhat serious) downside, the final result is pretty
much perfect: fields are first-class citizens (as lenses) and are not in
the same scope as identifiers. We've been using this extensively throughout
our whole project and it's been perfect—perhaps surprisingly, we haven't
run into any issues with type inference or type error messages (beyond what
you normally get with lens).

With this addition, Haskell records went from being a real blemish on the
language to being the best I've ever used. The orphan instance is a
definite red flag and you should absolutely *not* have that instance in a
library, but if you're working on a standalone executable or some extensive
internal code, I think it's absolutely worth it.

[1]: https://hackage.haskell.org/package/overloaded-records

[2]: https://hackage.haskell.org/package/generic-lens


On Sat, Dec 23, 2017 at 6:41 AM, Li-yao Xia <lysxia at gmail.com> wrote:

> I don't think "authorL" hurts readability. It just seems the logical
> choice if "author" is already taken.
>
> Have you seen generic-lens? The lens for the "author" field is  (field
> @"author") so there is some added noise compared to "authorL", but it can
> be used as a TH-free alternative to makeClassy.
>
> type Field name a = forall s. HasField name s s a a => Lens s s a a
>
> authorL :: Field "author" Author
> authorL = field @"author"
>
> Cheers,
> Li-yao
>
>
> On 12/23/2017 08:36 AM, ☂Josh Chia (謝任中) wrote:
>
>> Quite often, I need to use record types like this:
>>
>> data Whole1 = Whole1 { part :: Part, ... }
>> data Whole2 = Whole2 { part :: Part, ... }
>>
>> Where Whole1 & Whole2 are types of things that have a Part and some other
>> things. E.g. a Book has an Author, a Title, etc and so does an Article.
>>
>> The problem is that I'm not actually allowed to use the same name
>> (author/part) in two different record types. Some people use lens to solve
>> this. You can have a lens called 'author' for dealing with the Author in
>> both Book and Article (e.g. using makeClassy).
>>
>> That's fine, but there's yet another problem. Let's say I have a function
>> that takes an Author and a [Library] and returns all the Libraries that
>> have Books or Articles matching the Author. So:
>>
>> findAuthorLibraries :: Author -> [Library] -> [Library]
>> findAuthorLibraries author libraries = ...
>>
>> But I already have a lens called 'author' and ghc will complain about
>> shadowing. So, to avoid shadowing, should I use 'theAuthor' instead of
>> 'author' for the function argument? Or, should I name the lens
>> 'authorLens', 'authorL' or 'lAuthor' instead of 'author'? Prefixing with
>> 'the' is quite unreadable because whether or not an argument has that
>> prefix depends on whether there's a lens with a conflicting name so it adds
>> noise to the code. Adding a 'Lens' prefix to the 'author' lens also seems
>> quite an overbearing eyesore because for consistency I would have to use
>> the prefix for all my field-accessing lenses.
>>
>> Maybe I should use Lens.Control.TH.makeClassy and then define:
>>
>> findAuthorLibraries :: HasAuthor a => a -> [Library] -> [Library]
>> findAuthorLibraries hasAuthor libraries = ...
>>
>> But that may be making my function more complicated and general than I
>> want, affecting readability, simplicity, compilation time and maybe even
>> performance.
>>
>> In summary, I find that there are ways around the problem but they really
>> affect readability.
>>
>> I could also disable the warning about shadowing but that seems pretty
>> dangerous. It may be OK to disable the warning for the specific cases where
>> a function argument shadows something from the topmost scope, but GHC does
>> not allow such selective disabling of that warning.
>>
>> In a code base that deals mainly with concrete business logic, this
>> problem probably crops up more than in a code base that deals mainly with
>> more abstract things.
>>
>> What do people do to address this problem? Any recommendations or best
>> practices?
>>
>> Josh
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>>
>> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20171223/8a116e9a/attachment.html>


More information about the Haskell-Cafe mailing list