|
|
# First Class Labels
|
|
# First Class Labels
|
|
|
|
|
|
|
|
|
|
|
|
## The Opportunity
|
|
## The Opportunity
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Haskell's type class and instance language enables a form of logic
|
|
Haskell's type class and instance language enables a form of logic
|
|
|
meta-programming at the level of types. Since record system proposal can often
|
|
meta-programming at the level of types. Since record system proposal can often
|
|
|
be phrased as an instance of Qualified Types, this means that **many (not all!)
|
|
be phrased as an instance of Qualified Types, this means that **many (not all!)
|
| ... | @@ -11,8 +13,10 @@ Haskell library**. To work around the limitation of Haskell 98, *this tends to |
... | @@ -11,8 +13,10 @@ Haskell library**. To work around the limitation of Haskell 98, *this tends to |
|
|
require several language extensions*, as implemented in GHC and Hugs.
|
|
require several language extensions*, as implemented in GHC and Hugs.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Examples include
|
|
Examples include
|
|
|
|
|
|
|
|
|
|
|
|
- [ Strongly typed heterogeneous collections](http://homepages.cwi.nl/~ralf/HList/)
|
|
- [ Strongly typed heterogeneous collections](http://homepages.cwi.nl/~ralf/HList/)
|
|
|
- [attachment:ticket:92:Data.Record.hs](/attachment/ticket/92/Data.Record.hs)[](/raw-attachment/ticket/92/Data.Record.hs), which demonstrates an
|
|
- [attachment:ticket:92:Data.Record.hs](/attachment/ticket/92/Data.Record.hs)[](/raw-attachment/ticket/92/Data.Record.hs), which demonstrates an
|
|
|
implementation of something similar to Daan Leijen's extensible records
|
|
implementation of something similar to Daan Leijen's extensible records
|
| ... | @@ -22,12 +26,14 @@ Examples include |
... | @@ -22,12 +26,14 @@ Examples include |
|
|
## The Problem
|
|
## The Problem
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Independent of the specific record library, there needs to be a representation
|
|
Independent of the specific record library, there needs to be a representation
|
|
|
of record field labels, and as record field selection in theses libraries is
|
|
of record field labels, and as record field selection in theses libraries is
|
|
|
usually based on types, field labels need to be distinguishable by their
|
|
usually based on types, field labels need to be distinguishable by their
|
|
|
types. In principle, this can easily be achieved by declaring for each label a
|
|
types. In principle, this can easily be achieved by declaring for each label a
|
|
|
single-constructor data type:
|
|
single-constructor data type:
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
data LabelX = LabelX deriving (Read,Show)
|
|
data LabelX = LabelX deriving (Read,Show)
|
|
|
```
|
|
```
|
| ... | @@ -36,6 +42,7 @@ data LabelX = LabelX deriving (Read,Show) |
... | @@ -36,6 +42,7 @@ data LabelX = LabelX deriving (Read,Show) |
|
|
However, this approach quickly runs into pragmatic issues in multi-module
|
|
However, this approach quickly runs into pragmatic issues in multi-module
|
|
|
programming:
|
|
programming:
|
|
|
|
|
|
|
|
|
|
|
|
1. There needs to be a common origin for importing record field label declarations used accross several modules.
|
|
1. There needs to be a common origin for importing record field label declarations used accross several modules.
|
|
|
1. The labels occupy the same namespace as types and data constructors, and using qualified names as record field labels is awkward at best.
|
|
1. The labels occupy the same namespace as types and data constructors, and using qualified names as record field labels is awkward at best.
|
|
|
|
|
|
| ... | @@ -47,6 +54,7 @@ if we ever want to import A and B into the same module C (think OpenGL windows |
... | @@ -47,6 +54,7 @@ if we ever want to import A and B into the same module C (think OpenGL windows |
|
|
in a GUI), we are in trouble, because we have two "conflicting" declarations
|
|
in a GUI), we are in trouble, because we have two "conflicting" declarations
|
|
|
for PointX. Note that the following doesn't work!
|
|
for PointX. Note that the following doesn't work!
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
module A where
|
|
module A where
|
|
|
data PointX = PointX deriving Show
|
|
data PointX = PointX deriving Show
|
| ... | @@ -68,27 +76,36 @@ the labels doesn't help either: in spite of our intentions, A.PointX and |
... | @@ -68,27 +76,36 @@ the labels doesn't help either: in spite of our intentions, A.PointX and |
|
|
B.PointX are different types!
|
|
B.PointX are different types!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
With current Haskell, the only way around this is to modify the imports:
|
|
With current Haskell, the only way around this is to modify the imports:
|
|
|
introduce a new common ancestor module, say PointX, that declares the label
|
|
introduce a new common ancestor module, say PointX, that declares the label
|
|
|
PointX, and have both A and B import that. However, this is impractical: it
|
|
PointX, and have both A and B import that. However, this is impractical: it
|
|
|
breaks module composition, and there is no least upper bound in the import
|
|
breaks module composition, and there is no least upper bound in the import
|
|
|
hierarchy where we can safely place our label declarations once and for all.
|
|
hierarchy where we can safely place our label declarations once and for all.
|
|
|
|
|
|
|
|
|
|
|
|
## The Proposal
|
|
## The Proposal
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
**I propose to introduce implicitly declared typed labels as first-class values
|
|
**I propose to introduce implicitly declared typed labels as first-class values
|
|
|
into Haskell' ([ticket:92](https://gitlab.haskell.org//haskell/prime/issues/92))**.
|
|
into Haskell' ([ticket:92](https://gitlab.haskell.org//haskell/prime/issues/92))**.
|
|
|
|
|
|
|
|
|
|
|
|
### Options
|
|
### Options
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
**Option 1:**
|
|
**Option 1:**
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
make label declarations unneccessary, by reserving a separate namespace for
|
|
make label declarations unneccessary, by reserving a separate namespace for
|
|
|
labels and their types (to be concrete, prefix identifiers with '\#', so that
|
|
labels and their types (to be concrete, prefix identifiers with '\#', so that
|
|
|
we'd have `#pointX :: #PointX`).
|
|
we'd have `#pointX :: #PointX`).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
This would affect language and implementations in the same way as numeric,
|
|
This would affect language and implementations in the same way as numeric,
|
|
|
character, and string literals do. In particular, every occurrence of
|
|
character, and string literals do. In particular, every occurrence of
|
|
|
`'#'<identifier>` would be interpreted as a value of type `'#'<Identifier>`
|
|
`'#'<identifier>` would be interpreted as a value of type `'#'<Identifier>`
|
| ... | @@ -97,8 +114,10 @@ own namespace, identified by the prefix '\#', labels and their types would |
... | @@ -97,8 +114,10 @@ own namespace, identified by the prefix '\#', labels and their types would |
|
|
just be ordinary constants and types, respectively.
|
|
just be ordinary constants and types, respectively.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
With this option, the problematic example would look like this:
|
|
With this option, the problematic example would look like this:
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
module A where
|
|
module A where
|
|
|
main = print #pointX
|
|
main = print #pointX
|
| ... | @@ -112,22 +131,30 @@ import B |
... | @@ -112,22 +131,30 @@ import B |
|
|
main = print [#pointX,A.#pointX,B.#pointX] -- no conflicts here!
|
|
main = print [#pointX,A.#pointX,B.#pointX] -- no conflicts here!
|
|
|
```
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
**pro:** simple in use, labels have their own namespace, no conflicting imports, known to work
|
|
**pro:** simple in use, labels have their own namespace, no conflicting imports, known to work
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
**con:** need to give up some identifiable space in the language for labels and their types
|
|
**con:** need to give up some identifiable space in the language for labels and their types
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
**Option 2:**
|
|
**Option 2:**
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
make type sharing expressible (something like the sharing constraints in
|
|
make type sharing expressible (something like the sharing constraints in
|
|
|
Standard ML's module language, to allow you to say when two declarations from
|
|
Standard ML's module language, to allow you to say when two declarations from
|
|
|
different imports refer to the same type).
|
|
different imports refer to the same type).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
This would have a major impact on language and implementations. Assuming a
|
|
This would have a major impact on language and implementations. Assuming a
|
|
|
sharing declaration of the form
|
|
sharing declaration of the form
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
sharing <type1> <type2>
|
|
sharing <type1> <type2>
|
|
|
```
|
|
```
|
| ... | @@ -135,6 +162,7 @@ sharing declaration of the form |
... | @@ -135,6 +162,7 @@ sharing declaration of the form |
|
|
|
|
|
|
|
the implementation would have to:
|
|
the implementation would have to:
|
|
|
|
|
|
|
|
|
|
|
|
1. find the declarations of `type1` and `type2` and check them for structural equivalence
|
|
1. find the declarations of `type1` and `type2` and check them for structural equivalence
|
|
|
1. unify `type1` and `type2`, ie., interpret either of them as a synonym for the same underlying type
|
|
1. unify `type1` and `type2`, ie., interpret either of them as a synonym for the same underlying type
|
|
|
|
|
|
| ... | @@ -146,8 +174,10 @@ couldn't be named). For the current proposal, however, only a |
... | @@ -146,8 +174,10 @@ couldn't be named). For the current proposal, however, only a |
|
|
trivial part of that generality would be needed.
|
|
trivial part of that generality would be needed.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
With this option, the problematic example would look like this:
|
|
With this option, the problematic example would look like this:
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
module A where
|
|
module A where
|
|
|
data PointX = PointX deriving Show
|
|
data PointX = PointX deriving Show
|
| ... | @@ -164,11 +194,17 @@ sharing A.PointX B.PointX |
... | @@ -164,11 +194,17 @@ sharing A.PointX B.PointX |
|
|
main = print [PointX,A.PointX,B.PointX] -- no conflicts here!
|
|
main = print [PointX,A.PointX,B.PointX] -- no conflicts here!
|
|
|
```
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
**pro:** seems like a useful feature anyway
|
|
**pro:** seems like a useful feature anyway
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
**con:** more complex than needed for this proposal, and would be rather verbose in use
|
|
**con:** more complex than needed for this proposal, and would be rather verbose in use
|
|
|
|
|
|
|
|
**Option 3:**
|
|
|
|
|
|
|
|
|
|
**Option 3:**
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
introduce a common least upper bound for shared label imports. (to be
|
|
introduce a common least upper bound for shared label imports. (to be
|
| ... | @@ -176,24 +212,29 @@ concrete: there would be a module `Data.Label`, implicitly providing shared |
... | @@ -176,24 +212,29 @@ concrete: there would be a module `Data.Label`, implicitly providing shared |
|
|
declarations of any labels).
|
|
declarations of any labels).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
This would have a similarly small effect on the type system as Option 1, only
|
|
This would have a similarly small effect on the type system as Option 1, only
|
|
|
that instead of syntax, we'd use imports from the reserved module `Data.Label`
|
|
that instead of syntax, we'd use imports from the reserved module `Data.Label`
|
|
|
to identify what is a label and what is not.
|
|
to identify what is a label and what is not.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Whenever encountering an `import Data.Label(<identifier>)`, we interpret
|
|
Whenever encountering an `import Data.Label(<identifier>)`, we interpret
|
|
|
`Data.Label.<identifier>` as a constant of type `Data.Label.<Identifier>` and
|
|
`Data.Label.<identifier>` as a constant of type `Data.Label.<Identifier>` and
|
|
|
`<identifier>` as a constant of type `<Identifier>`. the difference to normal
|
|
`<identifier>` as a constant of type `<Identifier>`. the difference to normal
|
|
|
imports is that the compiler/type system needs to know about `Data.Label`.
|
|
imports is that the compiler/type system needs to know about `Data.Label`.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
In other words, `Data.Label` does not exist in source or object code, but as a
|
|
In other words, `Data.Label` does not exist in source or object code, but as a
|
|
|
hint for the compiler/type system. Any identifier imported from there is a
|
|
hint for the compiler/type system. Any identifier imported from there is a
|
|
|
label of its own type, nothing else can be imported from there.
|
|
label of its own type, nothing else can be imported from there.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
With this option, the problematic example would look like this:
|
|
With this option, the problematic example would look like this:
|
|
|
|
|
|
|
|
|
|
|
|
```wiki
|
|
```wiki
|
|
|
module A where
|
|
module A where
|
|
|
import Data.Label(pointX)
|
|
import Data.Label(pointX)
|
| ... | @@ -209,12 +250,17 @@ import B |
... | @@ -209,12 +250,17 @@ import B |
|
|
main = print [pointX,A.pointX,B.pointX] -- no conflicts here!
|
|
main = print [pointX,A.pointX,B.pointX] -- no conflicts here!
|
|
|
```
|
|
```
|
|
|
|
|
|
|
|
|
|
|
|
**pro:** no syntax extension or separate label namespace, no problems with common imports
|
|
**pro:** no syntax extension or separate label namespace, no problems with common imports
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
**con:** no separate label namespace, labels still need to be declared, by means of import
|
|
**con:** no separate label namespace, labels still need to be declared, by means of import
|
|
|
|
|
|
|
|
|
|
|
|
## Related Tickets and Links
|
|
## Related Tickets and Links
|
|
|
|
|
|
|
|
|
|
|
|
- [ticket:92](https://gitlab.haskell.org//haskell/prime/issues/92) add first class labels
|
|
- [ticket:92](https://gitlab.haskell.org//haskell/prime/issues/92) add first class labels
|
|
|
|
|
|
|
|
- [ticket:27](https://gitlab.haskell.org//haskell/prime/issues/27) tweak the existing records system (adopt: none)
|
|
- [ticket:27](https://gitlab.haskell.org//haskell/prime/issues/27) tweak the existing records system (adopt: none)
|
| ... | @@ -229,6 +275,10 @@ main = print [pointX,A.pointX,B.pointX] -- no conflicts here! |
... | @@ -229,6 +275,10 @@ main = print [pointX,A.pointX,B.pointX] -- no conflicts here! |
|
|
|
|
|
|
|
- [ Extensible records with scoped labels](http://www.cs.uu.nl/~daan/pubs.html)
|
|
- [ Extensible records with scoped labels](http://www.cs.uu.nl/~daan/pubs.html)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
- [ Strongly typed heterogeneous collections](http://homepages.cwi.nl/~ralf/HList/)
|
|
- [ Strongly typed heterogeneous collections](http://homepages.cwi.nl/~ralf/HList/)
|
|
|
|
|
|
|
|
- [ original Haskell' mailing list message](http://www.haskell.org//pipermail/haskell-prime/2006-February/000463.html) |
|
- [ original Haskell' mailing list message](http://www.haskell.org//pipermail/haskell-prime/2006-February/000463.html) |
|
\ No newline at end of file |
|
|