I’ve bouncing this idea around in my head for a while now, and after playing with some imaginary code, I thought I’d share it with the community to get some feedback. I guess you might consider this a preliminary proposal to see if its even worth investing more effort into the idea or creating an official proposal.
A disclaimer beforehand, I felt reluctant to even share this because I didn’t want this idea to potentially derail Richard’s Local Modules proposal, but I’ve become quite discouraged from reading all of the pushback against the proposal along with other proposals of similar nature (first class modules, Namespaces, etc).
Not that this pushback is bad, many opponents of these proposals brought up some valid points. But I’ve noticed the general sentiment with Haskell proposals is that the smaller and less invasive they are, the better chance they have of succeeding. So with that in mind, my preliminary proposal follows!
The Problem / Motivation
Duplicate record fields and data constructors. I want to write code like this:
data Person = Person
{ name :: Text, ... }
data Company = Company
{ name :: Text, ... }
-- Or
data Breakfast = Eggs | Banana
data Lunch = Sandwich | Banana
But I can’t without getting complaints about name
or Banana
already being used.
Workarounds
For records, there’s DuplicateRecordFields
, but this doesn’t help with record update syntax
As suggested in the convenience thread RecordWildCards
and OverloadedRecordUpdate
can also remedy the update issues, but OverloadedRecordUpdate
is experimental currently, and I personally do not like the syntax of RecordWildCards
- it feels cluttered to me, especially if I have to do something like:
modifyCompany Payload -> Company -> Company
modifyCompany payload oldCompany@Company{..} =
-- I.e I want to refer to company as a whole value + with the Record Wildcard
For duplicate data constructors, the only workaround is to either physically create separate modules for each data type, or to add some prefix to your type such as:
data Breakfast = BEggs | BBanana
data Lunch = LSandwich | LBanana
This workaround also works for record fields, but this solution is very unsatisfying.
Now one might “its just syntax, get over it”, but the point of this extension is to make haskell a more convenient language to use. We need to focus on convenience if we hope to attract a greater audience, and I believe my suggestion is a pretty boring and standard in relation to other languages.
The Proposal
According to GHC Documentation
… Given a datatype definition
data Foo = MkFoo { bar :: Int, baz :: String }
The following will be available:
- the type constructor
Foo
;- the data constructor
MkFoo
;- the fields
bar
andbaz
for record construction, update, and pattern matching; and- the selector functions
bar :: Foo -> Int
andbaz :: Foo -> String
.
With this in mind, we add a language extension QualifiedData
which sticks the declarations of 2-4 in some sort of implicit module given the same name as the type itself; in the above case: Foo
.
With this in mind, we add a language extension QualifiedData
which changes the above rules to:
The following will be available:
- the type constructor
Foo
; (No change)- An local module
Foo
;- the data constructor
MkFoo
within moduleFoo
;- the fields
bar
andbaz
for record construction, update, and pattern matching;
4b. the fields of rule 4 are also created within moduleFoo
; and- the selector functions
bar :: Foo -> Int
andbaz :: Foo -> String
are created within moduleFoo
This means (when QualifiedData is enabled)
- The data constructor for foo would be
Foo.MkFoo
- To construct a
MkFoo
, you could say:
Foo.MkFoo { Foo.bar = 12, Foo.baz = "Baz" }
or
Foo.MkFoo { bar = 12, baz = 12 }
- To update a record
foo
with a value ofMkFoo
, you say:foo { Foo.bar = 12, Foo.baz = "baz" }
- Record selectors would take the form
Foo.bar someFoo
This would be applied to all data
declarations for any module the extension was enabled in.
(I don’t think theres much point in using this for newtype
on further reflection)
The benefits:
-
It automatically solves both duplicate record fields and duplicate data constructors without requiring any other extensions. (I think… I could be wrong )
-
It makes field selectors less problematic because they no longer pollute the general term namespace. I know some people don’t feel fond of field selectors, but I have found them handy on occasion to use, such as when doing some type of
fmap
. -
It doesn’t require a change in any library code out in the wild. Everyone who doesn’t want it writes haskell code the same as usual. Everyone who does want it gets to all of their data types behind an implicit module without bothering others.
Caveats
I’ve thought of one caveat to point 3. The following code is currently illegal in haskell today
data Breakfast = Eggs | Banana
data Lunch = Sandwich | Banana
This gives the error Multiple declarations of Banana
. Using QualifiedData
should prevent this error from being raised, but how do consumers of this module deal with this without requiring them to enable QualifiedData
?
One workaround I can think of here is to conditionally add a prefix to the data constructors so that they become something like:
data Breakfast = BreakfastEggs | BreakfastBanana
data Lunch = LunchSandwich | LunchBanana
Is this even a possible workaround? I don’t know enough about the implementation of GHC to know if this can even be done.
Edit: Actually. the more I think about this, the more I realize this isn’t a valid workaround. Even if it was, it’d probably create confusion. I’ll think about this point a bit more. Suggestions are welcome as well
Other notes and comparisons:
Compared to the other proposals such as Local Modules
, First Class Modules
, or Namespaces
, this proposal is far less powerful. But one might consider this an advantage since it avoids lot of the pitfalls and edge cases of the other proposals. We dont have to worry about the various ways exporting submodules could impact users and how this interacts with using/not-using local modules.
What I like about the Local Modules
proposal over this one is that it feels like a more general purpose and more composable solution. But I hope (maybe naively) that it might be possible to implement this in such a way that it lays the ground work for a more proper Local modules
implementation, and also reaps us some benefits along the way.
Some Example code
When I was first playing with this idea, I wrote the following imaginary code. I leave it here just so you can see the extension in action
Some plain old file: SomeModule.hs
module SomeModule where
data FooType
= Foo
| Bar
| Baz
data Person
= Person { name :: Text, age :: Int }
And a main module Main.hs
where QualifiedData is used
{-# LANGUAGE QualifiedData #-}
module Main where
import SomeModule (FooType(..), Person(..))
showFooType :: FooType -> String
showFooType f = case f of
FooType.Foo -> "foo"
FooType.Bar -> "bar"
FooType.Baz -> "baz"
createPerson :: Text -> Int -> Person
createPerson name age =
Person { Person.name = name, Person.age = age }
testPerson :: Person -> String
testPerson p =
p { Person.name = "hello" }
What I hope to gain from this post is some general feedback, yays and nays! And perhaps guidance on how this proposal might be refined if refinement is needed and people are generally in favor of this in general
Thanks for taking the time to read this!