... | ... | @@ -588,7 +588,7 @@ will no longer work as importing `A(..)` will import the type `A` and the constr |
|
|
new patterns but the usage of pattern synonyms should be transparent to the end user. What's needed is to be able to
|
|
|
associate the new synonyms with a type such that client code is oblivious to this implementation.
|
|
|
|
|
|
### Proposal 1
|
|
|
### Proposal
|
|
|
|
|
|
|
|
|
Richard proposes that synonyms are associated at the export of a datatype. Our running example would then look as follows:
|
... | ... | @@ -604,36 +604,82 @@ pattern MkA n = A (Just n) |
|
|
pattern NoA = A Nothing
|
|
|
```
|
|
|
|
|
|
### Proposal 2
|
|
|
### Specification
|
|
|
|
|
|
|
|
|
Simon proposes that synonyms are associated at the definition of a datatype. Our running example would look as follows:
|
|
|
This proposal only changes module imports and exports.
|
|
|
|
|
|
```wiki
|
|
|
{-# LANGUAGE PatternSynonyms #-}
|
|
|
module Internal(A(MkA, NoA)) where
|
|
|
#### Definition
|
|
|
|
|
|
newtype A = NewA (Just Int)
|
|
|
with (MkA, NoA)
|
|
|
|
|
|
pattern MkA n = A (Just n)
|
|
|
We say that "a pattern synonym `P` is associated with a type `T` relative to module `M`" if and only if "`M` exports `T` whilst associating `P`".
|
|
|
|
|
|
pattern NoA = A Nothing
|
|
|
#### Exports
|
|
|
|
|
|
|
|
|
For any modules `M``N`, we say that "`M` exports `T` whilst associating `P`" just when
|
|
|
|
|
|
- The export has the form `T(c1, ..., cn, P)` where c1 to cn (n \>= 0) are a mixture of other field names, constructors, pattern synonyms and the special token `..`. The special token `..`, which indicates either
|
|
|
|
|
|
1. all constructors and field names from `T`'s declaration, if `T` is declared in this module; or
|
|
|
1. all symbols imported with `T`, which might perhaps include patterns associated with `T` in some other module. In case (2), `..` might in fact be a union of sets, if `T` is imported from multiple modules with different sets of associated definitions.
|
|
|
|
|
|
#### Imports
|
|
|
|
|
|
|
|
|
For any modules `M``N`, if we import `N` from `M`,
|
|
|
|
|
|
- The abbreviated form `T(..)` brings into scope all the constructors, methods or field names exported by `N` as well any patterns associated with `T` relative to `N`.
|
|
|
- The explicit form `T(c1,...,cn)` can name any constructors, methods or field names exported by `N` as well as any patterns associated with `T` relative to `N`.
|
|
|
|
|
|
#### Clarification
|
|
|
|
|
|
- Associated patterns are typechecked to ensure that their type matches the type they are associated with.
|
|
|
|
|
|
- Hence, all synonyms must be initially explicitly associated but a module which imports an associated synonym is oblivious to whether they import a synonym or a constructor.
|
|
|
|
|
|
- According to this proposal, only pattern synonyms may be associated with a datatype. But it would be trivial to expand this proposal to allow arbitrary associations.
|
|
|
|
|
|
#### Examples
|
|
|
|
|
|
```
|
|
|
moduleN(T(..,P))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleMwhereimportN(T(..))
|
|
|
```
|
|
|
|
|
|
`P` is associated with `T` relative to `N`. M imports `T`, `MkT` and `P`.
|
|
|
|
|
|
In the rest of the discussion I refer to Richard's suggestion rather than Simon's refinement.
|
|
|
Consider two packages `old-rep` and `new-rep` which have different representations of the same structure.
|
|
|
The library author wants to smooth the transition for his users by providing a compatibility package `compat-rep`
|
|
|
so that code using the old representation in `old-rep` can work seamlessly with `new-rep`.
|
|
|
```
|
|
|
moduleN(T(..))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleMwhereimportN(T(..))
|
|
|
```
|
|
|
|
|
|
`P` is unassociated. `M` imports `T` and `MkT`.
|
|
|
|
|
|
The problem is to define `compat-rep` such that by changing the dependencies of our package, our code to continues to work
|
|
|
but without depending on `old-rep`. More generally, an author may want to write a `*-compat` package for two packages which they do
|
|
|
not control. Having to define these synonyms at the definition site is too restrictive for this case .
|
|
|
```
|
|
|
moduleN(T(P))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleMwhereimportN(T(..))
|
|
|
```
|
|
|
|
|
|
`P` is associated with `T` relative to `N`. M imports `T`, and `P`.
|
|
|
|
|
|
```
|
|
|
moduleN(T(P))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleM(T(..))whereimportN(T(..))-- O.hsmoduleOwhereimportM(T(..))
|
|
|
```
|
|
|
|
|
|
`P` is associated with `T` relative to `N`.
|
|
|
|
|
|
|
|
|
As `M` imports `N` and imports `T`, `P` is associated with `T` relative to `M`. Thus `M` exports `T` and `P`.
|
|
|
|
|
|
In both cases it is noted that the type of the associated synonym should be checked to ensure it matches with the other constructors.
|
|
|
|
|
|
Therefore when `O` imports `T(..)` from `M`, it imports `T` and `P`.
|
|
|
|
|
|
```
|
|
|
moduleN(T(..))wheredataT=MkTInt-- M.hsmoduleM(T(P))whereimportN(T(..))patternP=MkT5-- O.hsmoduleOwhereimportM(T(..))
|
|
|
```
|
|
|
|
|
|
|
|
|
This example highlights being able to freely reassociate synonyms.
|
|
|
|
|
|
`M` imports `T` and `MkT` from `N` but then as `M` associates `P` with `T`, when `O` imports `M`, `T` and `P` are brought into scope.
|
|
|
|
|
|
### Unnatural Association
|
|
|
|
... | ... | @@ -679,110 +725,32 @@ pattern P x <- (destruct -> x) |
|
|
|
|
|
I propose that we allow such synonyms to be associated with a type `T` as long as it typechecks. I don't expect this to be much used in practice.
|
|
|
|
|
|
### Specification
|
|
|
|
|
|
|
|
|
This proposal only changes module imports and exports.
|
|
|
|
|
|
#### Definition
|
|
|
|
|
|
|
|
|
We say that "a pattern synonym `P` is associated with a type `T` relative to module `M`" if and only if "`M` exports `T` whilst associating `P`".
|
|
|
|
|
|
**SLPJ**: this definition simply defines one three-place term in terms of another equally-undefined three-place term. Would be possible to abandon one form of words or the other.
|
|
|
|
|
|
#### Exports
|
|
|
|
|
|
**SLPJ** OK here comes the definition of the latter term. Good.
|
|
|
### Associatation at definition
|
|
|
|
|
|
|
|
|
For any modules `M``N`, we say that "`M` exports `T` whilst associating `P`" either when
|
|
|
|
|
|
- The export has the form `T(c1, ..., cn, P)` where c1 to cn are a mixture of other field names, constructors and pattern synonyms.
|
|
|
|
|
|
>
|
|
|
> This mixture of other stuff may include the special token `..`, which indicates either 1) all constructors and field names from `T`'s declaration, if `T` is declared in this module; or 2) all symbols imported with `T`, which might perhaps include patterns associated with `T` in some other module. In case (2), `..` might in fact be a union of sets, if `T` is imported from multiple modules with different sets of associated definitions.
|
|
|
|
|
|
**SLPJ** This seems odd. Example:
|
|
|
Simon proposed that synonyms are associated at the definition of a datatype. Our running example would look as follows:
|
|
|
|
|
|
```wiki
|
|
|
module M( T(A,B,P) ) where
|
|
|
data T = A | B
|
|
|
pattern P = Nothing
|
|
|
```
|
|
|
|
|
|
|
|
|
Is this ok? Does `M` export `T` whilst associating `P`? Do you really mean to allow pattern synonyms to be associated with entirely unrelated types?
|
|
|
|
|
|
**MP** Yes, this is ok with the current proposal.
|
|
|
|
|
|
|
|
|
Can a pattern synonym be associated with more than one type?
|
|
|
|
|
|
**MP** Yes, this could also be useful in the case of polymorphic synonyms such as the example in the above section.
|
|
|
|
|
|
|
|
|
Could you give examples ti illustrate the re-export thing? Which I do not understand.
|
|
|
|
|
|
**MP** I have added examples in a new section below.
|
|
|
|
|
|
**SLPJ** this second bullet does not seem to be part of the definition of "`M` exports `T` whilst associating `P`". Correct?
|
|
|
|
|
|
**MP** Ah, I see how Richard's edits seemed to have confused this a bit. I don't think it's necessary anymore.
|
|
|
|
|
|
#### Imports
|
|
|
|
|
|
|
|
|
For any modules `M``N`, if we import `N` from `M`,
|
|
|
|
|
|
- The abbreviated form `T(..)` brings into scope all the constructors, methods or field names exported by `N` as well any patterns associated with `T` relative to `N`.
|
|
|
- The explicit form `T(c1,...,cn)` can name any constructors, methods or field names exported by `N` as well as any patterns associated with `T` relative to `N`.
|
|
|
|
|
|
#### Clarification
|
|
|
|
|
|
- Associated patterns are **not** typechecked to ensure that their type matches the type they are associated with.
|
|
|
|
|
|
- Hence, all synonyms must be initially explicitly associated but a module which imports an associated synonym is oblivious to whether they import a synonym or a constructor.
|
|
|
|
|
|
- According to this proposal, only pattern synonyms may be associated with a datatype. But it would be trivial to expand this proposal to allow arbitrary associations.
|
|
|
|
|
|
#### Examples
|
|
|
|
|
|
```
|
|
|
moduleN(T(..,P))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleMwhereimportN(T(..))
|
|
|
```
|
|
|
|
|
|
`P` is associated with `T` relative to `N`. M imports `T`, `MkT` and `P`.
|
|
|
|
|
|
```
|
|
|
moduleN(T(..))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleMwhereimportN(T(..))
|
|
|
```
|
|
|
|
|
|
`P` is unassociated. `M` imports `T` and `MkT`.
|
|
|
{-# LANGUAGE PatternSynonyms #-}
|
|
|
module Internal(A(MkA, NoA)) where
|
|
|
|
|
|
```
|
|
|
moduleN(T(P))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleMwhereimportN(T(..))
|
|
|
```
|
|
|
newtype A = NewA (Just Int)
|
|
|
with (MkA, NoA)
|
|
|
|
|
|
`P` is associated with `T` relative to `N`. M imports `T`, and `P`.
|
|
|
pattern MkA n = A (Just n)
|
|
|
|
|
|
pattern NoA = A Nothing
|
|
|
```
|
|
|
moduleN(T(P))wheredataT=MkTIntpatternP=MkT5-- M.hsmoduleM(T(..))whereimportN(T(..))-- O.hsmoduleOwhereimportM(T(..))
|
|
|
```
|
|
|
|
|
|
`P` is associated with `T` relative to `N`.
|
|
|
|
|
|
|
|
|
As `M` imports `N` and imports `T`, `P` is associated with `T` relative to `M`. Thus `M` exports `T` and `P`.
|
|
|
|
|
|
The proposal refers to Richard's suggestion rather than Simon's refinement for the following reasons.
|
|
|
|
|
|
Therefore when `O` imports `T(..)` from `M`, it imports `T` and `P`.
|
|
|
|
|
|
```
|
|
|
moduleN(T(..))wheredataT=MkTInt-- M.hsmoduleM(T(P))whereimportN(T(..))patternP=MkT5-- O.hsmoduleOwhereimportM(T(..))
|
|
|
```
|
|
|
|
|
|
Consider two packages `old-rep` and `new-rep` which have different representations of the same structure.
|
|
|
The library author wants to smooth the transition for his users by providing a compatibility package `compat-rep`
|
|
|
so that code using the old representation in `old-rep` can work seamlessly with `new-rep`.
|
|
|
|
|
|
This example highlights being able to freely reassociate synonyms.
|
|
|
|
|
|
`M` imports `T` and `MkT` from `N` but then as `M` associates `P` with `T`, when `O` imports `M`, `T` and `P` are brought into scope. |
|
|
The problem is to define `compat-rep` such that by changing the dependencies of our package, our code to continues to work
|
|
|
but without depending on `old-rep`. More generally, an author may want to write a `*-compat` package for two packages which they do
|
|
|
not control. Having to define these synonyms at the definition site is too restrictive for this case . |