|
|
|
# Proposal: [StricterLabelledFieldSyntax](stricter-labelled-field-syntax)
|
|
|
|
|
|
|
|
<table><tr><th> Ticket </th>
|
|
|
|
<th>[\#132](https://gitlab.haskell.org//haskell/prime/issues/132)</th></tr>
|
|
|
|
<tr><th> Dependencies </th>
|
|
|
|
<th> none
|
|
|
|
</th></tr>
|
|
|
|
<tr><th> Related </th>
|
|
|
|
<th> none
|
|
|
|
</th></tr></table>
|
|
|
|
|
|
|
|
## Compiler support
|
|
|
|
|
|
|
|
<table><tr><th> GHC </th>
|
|
|
|
<th> partial (test patch available)
|
|
|
|
</th></tr>
|
|
|
|
<tr><th> nhc98 </th>
|
|
|
|
<th> none
|
|
|
|
</th></tr>
|
|
|
|
<tr><th> Hugs </th>
|
|
|
|
<th> none
|
|
|
|
</th></tr>
|
|
|
|
<tr><th> UHC </th>
|
|
|
|
<th> none
|
|
|
|
</th></tr>
|
|
|
|
<tr><th> JHC </th>
|
|
|
|
<th> none
|
|
|
|
</th></tr>
|
|
|
|
<tr><th> LHC </th>
|
|
|
|
<th> none
|
|
|
|
</th></tr></table>
|
|
|
|
|
|
|
|
## Summary
|
|
|
|
|
|
|
|
|
|
|
|
Make the labelled field syntax stricter, so that unclear code is illegal.
|
|
|
|
|
|
|
|
## Description
|
|
|
|
|
|
|
|
|
|
|
|
Many people believe that the precedence of labelled fields creation, updates and pattern matching can lead to confusing code. For example, in [ http://hackage.haskell.org/trac/ghc/ticket/2530](http://hackage.haskell.org/trac/ghc/ticket/2530) it was reported that this program:
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
module Main where
|
|
|
|
|
|
|
|
data A = A {x :: Int} deriving (Show)
|
|
|
|
|
|
|
|
main :: IO ()
|
|
|
|
main = print $ Just A {x = 5}
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
(correctly, according to Haskell 98) prints
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
Just A {x = 5}
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
in hugs, but the more easily comprehendible
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
Just (A {x = 5})
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
in ghci.
|
|
|
|
|
|
|
|
|
|
|
|
According to Haskell 98,
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
A {x = 5}
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
is an atomic expression - but it doesn't look atomic! This violates the principle of least surprise.
|
|
|
|
|
|
|
|
|
|
|
|
Before coming across labelled fields, but having had "function application binds tightest" drummed into you to understand how to read expressions containing a mixture of applications and infix operators, of the following 2 functions:
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
data A = A {x :: Bool} deriving (Show)
|
|
|
|
|
|
|
|
f = print $ Just A {x = True}
|
|
|
|
g = print $ A True {x = False}
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
I would expect `g` to be the correct one, while it is `f` that is correct according to Haskell 98.
|
|
|
|
|
|
|
|
|
|
|
|
However, once you remove the space before the curly brace:
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
h = print $ Just A{x = True}
|
|
|
|
i = print $ A True{x = False}
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
it is `h` that looks more correct. Note that we have a similar problem with infix operators, and expressions like
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
1+f x+2
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
I propose that all of `f`, `g`, `h` and `i` be made illegal, with parentheses being required to disambiguate these cases.
|
|
|
|
|
|
|
|
|
|
|
|
Here are some real-life examples of what I consider confusing code, from `haskeline`:
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
metaKey :: Key -> Key
|
|
|
|
metaKey (Key m bc) = Key m {hasMeta = True} bc
|
|
|
|
```
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
searchText :: SearchEntry -> [Grapheme]
|
|
|
|
searchText SearchEntry {entryState = IMode xs ys} = reverse xs ++ ys
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
and from `Cabal`:
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
configure ... = do
|
|
|
|
...
|
|
|
|
(ghcPkgProg, ghcPkgVersion, conf'') <-
|
|
|
|
requireProgramVersion verbosity ghcPkgProgram {
|
|
|
|
programFindLocation = guessGhcPkgFromGhcPath ghcProg
|
|
|
|
}
|
|
|
|
anyVersion (userMaybeSpecifyPath "ghc-pkg" hcPkgPath conf')
|
|
|
|
...
|
|
|
|
```
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo
|
|
|
|
-> Executable -> ComponentLocalBuildInfo -> IO ()
|
|
|
|
buildExe verbosity _pkg_descr lbi
|
|
|
|
exe@Executable { exeName = exeName', modulePath = modPath } clbi = do
|
|
|
|
...
|
|
|
|
```
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
case PackageIndex.lookupPackageName index (PackageName "rts") of
|
|
|
|
[rts] -> PackageIndex.insert rts { Installed.ldOptions = [] } index
|
|
|
|
```
|
|
|
|
|
|
|
|
```wiki
|
|
|
|
register pkg@PackageDescription { library = Just lib }
|
|
|
|
lbi@LocalBuildInfo { libraryConfig = Just clbi } regFlags
|
|
|
|
= ...
|
|
|
|
```
|
|
|
|
|
|
|
|
## References
|
|
|
|
|
|
|
|
|
|
|
|
A patch to add support for the syntax to GHC, as well as patches needed to fix GHC and the libraries to follow the new syntax, are in the ticket ([\#132](https://gitlab.haskell.org//haskell/prime/issues/132)).
|
|
|
|
|
|
|
|
## Report Delta
|
|
|
|
|
|
|
|
|
|
|
|
In [ Section 3](http://haskell.org/onlinereport/exps.html#sect3) replace:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
exp10 -> ...
|
|
|
|
| fexp
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
with:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
exp10 -> ...
|
|
|
|
| recexp
|
|
|
|
recexp -> qcon { fbind1 , ... , fbindn } (labeled construction, n >= 0)
|
|
|
|
| aexp<qcon> { fbind1 , ... , fbindn } (labeled update, n >= 1)
|
|
|
|
| fexp
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
and remove:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
aexp -> ...
|
|
|
|
| qcon { fbind1 , ... , fbindn } (labeled construction, n>=0)
|
|
|
|
| aexp<qcon> { fbind1 , ... , fbindn } (labeled update, n >= 1)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
In [ Section 3.15.2](http://haskell.org/onlinereport/exps.html#sect3.15.2) replace:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
aexp -> qcon { fbind1 , ... , fbindn } (labeled construction, n>=0)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
with:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
recexp -> qcon { fbind1 , ... , fbindn } (labeled construction, n >= 0)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
In [ Section 3.15.3](http://haskell.org/onlinereport/exps.html#sect3.15.3) replace:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
aexp -> aexp<qcon> { fbind1 , ... , fbindn } (labeled update, n >= 1)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
with:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
recexp -> aexp<qcon> { fbind1 , ... , fbindn } (labeled update, n >= 1)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
In [ Section 3.17.1](http://haskell.org/onlinereport/exps.html#sect3.17.1) replace:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
pat10 -> ...
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
with:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
pat10 -> ...
|
|
|
|
| qcon { fpat1 , ... , fpatk } (labeled pattern, k >= 0)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
and remove:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
apat -> ...
|
|
|
|
| qcon { fpat1 , ... , fpatk } (labeled pattern, k>=0)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
In [ Section 9.5](http://haskell.org/onlinereport/syntax-iso.html#sect9.5) replace:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
exp10 -> ...
|
|
|
|
| fexp
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
with:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
exp10 -> ...
|
|
|
|
| recexp
|
|
|
|
recexp -> qcon { fbind1 , ... , fbindn } (labeled construction, n >= 0)
|
|
|
|
| aexp<qcon> { fbind1 , ... , fbindn } (labeled update, n >= 1)
|
|
|
|
| fexp
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
and remove:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
aexp -> ...
|
|
|
|
| qcon { fbind1 , ... , fbindn } (labeled construction, n>=0)
|
|
|
|
| aexp<qcon> { fbind1 , ... , fbindn } (labeled update, n >= 1)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
and replace
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
pat10 -> ...
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
with:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
pat10 -> ...
|
|
|
|
| qcon { fpat1 , ... , fpatk } (labeled pattern, k >= 0)
|
|
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
and remove:
|
|
|
|
|
|
|
|
```
|
|
|
|
|
|
|
|
apat -> ...
|
|
|
|
| qcon { fpat1 , ... , fpatk } (labeled pattern, k>=0)
|
|
|
|
``` |
|
|
\ No newline at end of file |