Extraneous parentheses required to parse kind signature on the RHS of a type synonym
After D5173, the restrictions about where kind signatures can appear in the source were significantly relaxed so that things like:
type family F where
F = Int :: Type
Are now allowed. However, there appears to be one case that was missed in that patch: the right-hand sides of type synonyms. For instance, I would expect the following to parse:
{-# LANGUAGE KindSignatures #-}
module Bug where
import Data.Kind
type F = Int :: Type
However, even GHC HEAD still refuses to parse this:
$ /opt/ghc/head/bin/ghci Bug.hs
GHCi, version 8.7.20181015: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:6:14: error: parse error on input ‘::’
|
6 | type F = Int :: Type
| ^^
Luckily, I don't think this will be too difficult to fix, since all that needs to be done is to update the parser production for type synonyms to use something like ktype
instead of ctype
. Patch incoming.
Trac metadata
Trac field | Value |
---|---|
Version | 8.7 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (Parser) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |