{-# 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”.
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.
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!
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!
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.
Them’s fighting words 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.
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.
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 But we should of course keep the old mechanism available for as long as necessary, or even indefinitely.
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?
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.
Them’s fighting words 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!