What are you supposed to do about -Wambiguous-fields?

Hello folks, if you try compiling the module

{-# LANGUAGE DuplicateRecordFields #-}

module Junk where

data Foo = Foo { foo :: Int }

data Bar = Bar { foo :: Int }

blah :: Bar -> Bar
blah bar = bar { foo = 5 }

you’ll get the warning

junk.hs:10:18: warning: [GHC-02256] [-Wambiguous-fields]
    Ambiguous record update with parent type constructor ‘Bar’.
    This type-directed disambiguation mechanism will not be supported by -XDuplicateRecordFields in future releases of GHC.
    Consider disambiguating using module qualification instead.
   |
10 | blah bar = bar { foo = 5 }
   |                  ^^^^^^

but I don’t understand the suggestion to “use module qualification instead”.

3 Likes

I guess It means: "put each type in a different module and then update with bar {Bar.foo = 5}" (asuming you imported some module qualified as Bar)

You don’t necessarily have to put each type in a different module, because you can do something like

import qualified Mod (Foo(..)) as Foo
import qualified Mod (Bar(..)) as Bar

and use Foo.foo and Bar.foo unambiguously. See here:

3 Likes

Ah ha! Okay.

In my case, I have two internal helper types that share a record field name.

I structured the types this way because with

  • DuplicateRecordFields
  • NoFieldSelectors
  • OverloadedRecordDot

the getter story is actually rather nice! foo.bar syntax just works, and I don’t have to worry about bar polluting the namespace.

… but it seems updating is still somewhat fraught! So, perhaps generic-lens is the cleanest solution for this problem today.

Also be aware of proposal #537, which is still open. I wouldn’t expect to see type-directed disambiguation go away for some time, because there are still a few things to work out.

No, optics is. I’ve explained why way too many times though, time to give up I guess. Enjoy shitty long compilation times and bad error messages.

EDIT: @mitchellwrosen btw, nothing personal man, I’m just frustrated because:

  1. A long time ago I tried to improve generic-lens-core etc. and my PRs were ignored because the repo was abandoned.
  2. I optimized the shit out of generic optics wrt. compilation times, runtime efficiency and user experience and integrated them into optics proper.
  3. I wrote a lot of documentation in optics for this.
  4. Over the years in multiple places I explained that optics has generic optics integrated and they behave better than generic-lens on all fronts.
  5. People still mention generic-lens most of the time as their first choice when it comes to this.

So you just triggered the bomb. Now however I can say that I learned my lesson and I’m officially done with the point (4).

7 Likes

Okay, good to know!

To be quite honest (as you can probably tell by this thread) my general Haskell dependency and language knowledge is probably 5-10 years out of date. So I can’t help but feel you have taken the wrong lesson here regarding your point (4)… you’ve got at least one new (potential) user as of today!

4 Likes

I thought we were supposed to migrate to OverloadedRecordUpdate. At least, that’s what I was planning on doing. What’s wrong with this? It seems much better than module-qualifying field names.

{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedRecordUpdate #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE FunctionalDependencies #-}

import Prelude

data Foo = Foo { foo :: Int }
data Bar = Bar { foo :: Int }

-- Of course this should ultimately be shipped with base, or at least
-- a library that comes with GHC.  So far we only have
--
-- https://www.stackage.org/haddock/lts-22.21/base-4.18.2.1/GHC-Records.html#t:HasField
class GetSetField fieldName t fieldType | t fieldName -> fieldType where
  getField :: t -> fieldType
  setField :: t -> fieldType -> t

-- Inferred type:
--
-- blah :: (GetSetField "foo" t fieldType, Num fieldType) => t -> t
--
-- (AllowAmbiguousTypes is needed for this type)
blah x = x { foo = 5 }

Please don’t give up! This is the first time I’ve heard that optics supports this functionality. I suspect a lot more people need to hear the message!

4 Likes

Great to see this question asked here as well. I’m working on a rather large code base that uses DuplicateRecordFields.

We’re getting warnings about ambiguous record fields now and we’re largely just disabling these. I know this is footgun because this is going to be an error but I really don’t know a way forward here.

Moreover, it is extremely unintuitive; The approach of disambiguating field names by type seems completely sensible to me in a language like Haskell, I would even go as far and say this is something where types are really unambiguously good and unproblematic, I know that the reason of introducing this is a technical reason, however, I don’t see how such a reason can be the cause of such an unintuitive and (I think it will be) disruptive change.

What I expect at least is a good way forward. Importing the own module qualified is not something I would count as a good way forward.

In retrospect I would’ve been happier if DuplicateRecordField was either never introduced or the type based disambiguating was kept.

For the future I hope there will be a real solution as soon as this becomes an error.

2 Likes

Them’s fighting words :smiley: Type-directed name resolution is controversial in languages with type inference because it generates an ugly chicken-egg problem: In order to generate constraints to find out the types of the program you have to know what the types of the identifiers (in this case, the record selectors) in your program are, but with type-directed name resolution you first have to know the types in order to find out what the identifier stands for, and what type signature it has. The old mechanism used an ad-hoc way of solving this problem; the main advantage of RecordDot syntax, in my opinion, is that it uses typeclasses for the name-resolution part, which is much better integrated into the type inference of GHC.

So I absolutely agree that we should use the types to infer the right record accessors, but we should use the better mechanism for it that GHC provides, i.e. typeclasses and the HasField typeclass.

3 Likes

that would be great, I hope that this mechanism will arrive in time before we remove support for ambiguous record fields. Otherwise I suspect that would cause a lot of trouble.

1 Like

I already completely switched several projects to record dot syntax for accessing record fields, together with NoFieldSelectors, and I really liked it. In my opinion it also makes the code more readable, because function application and field access are more visually distinct, but on that point opinions may vary. As soon as record update is properly stabilized I will no longer look back on the old record syntax and exclusively use the new one :slight_smile: But we should of course keep the old mechanism available for as long as necessary, or even indefinitely.

1 Like

But doesn’t the replacement already exist? That is, OverloadedRecordDot and OverloadedRecordUpdate? I still don’t understand what people think that they are lacking. See also What are you supposed to do about -Wambiguous-fields? - #8 by tomjaguarpaw.

EDIT: Corrected extension names

I didn’t know RecordUpdateSyntax, where would I be able to find information about it? Doesn’t look like it’s in GHC 9.10. (RebindableSyntax is not an option in the general case)

It also appears that the compiler doesn’t generated setField yet, does it?

https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/overloaded_record_update.html

What I meant is the OverloadedRecordUpdate extension, which is still marked as experimental in the user guide.

Sorry, I got the extension names wrong: they should be OverloadedRecordDot and OverloadedRecordUpdate.

Right, and we have the guarantee that ambiguous field selector/update usage will not be removed until this replacement (or some other) stabilises:

In a subsequent GHC release, remove support for ambiguous field selector/update occurrences entirely and remove the warning. This step should not be taken until RecordDotSyntax or another generally-accepted mechanism for disambiguation is available, to provide users with a clear alternative.

Not as far as I know. It sounds like something that should be derived anyway, but I don’t know the best way of doing that.

The warning GHC-02256 also wasn’t documented yet, so I started a PR to document the warning in the error message index. I currently have one example which uses the solution that @adamgundry proposes, but I am happy to add other solutions as well :slight_smile:
The PR is here: Document GHC-02256 by BinderDavid · Pull Request #484 · haskellfoundation/error-message-index · GitHub

I would also be grateful for suggestions on how to improve the explanation of the warning.

2 Likes

for playing around:
https://bin.mangoiv.com/note?id=f876d8ce-3a7a-4acf-9ce7-adb348d44b5b

edit: yes I know it should be (name :: Symbol) cause otherwise we don’t get an instance but mmh this is hacked together

Thanks to @MangoIV and @DavidB I can provide some answers:

  • OverloadedRecordUpdate is considered experimental.
  • There is no definitive story for generating getField for OverloadedRecordDot.
  • There is not even a blessed class for setField, for OverloadedRecordUpdate.

Them’s fighting words :smiley: Type-directed name resolution is controversial in languages with type inference because it generates an ugly chicken-egg problem

One unintuitive thing for me: why is type inference involved at all? In my example, I should think that the type checker could use my user-written type signature as a constraint: bar : Bar.

blah :: Bar -> Bar
blah bar = bar { foo = 5 }

Rather, this ambiguous nugget seems to be considered in isolation at some point, generating the warning.

{ foo = 5 }

But I don’t need GHC to work so hard; I want to assert what type the record is!