[GHC] #16024: Kind Signatures on data instances
GHC
ghc-devs at haskell.org
Mon Dec 10 01:09:47 UTC 2018
#16024: Kind Signatures on data instances
-------------------------------------+-------------------------------------
Reporter: andrewthad | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.3
Component: Compiler | Version: 8.6.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
There's a comment in `compiler/typecheck/TcInstDcls.hs` that reads:
> The "header" is the part other than the data constructors themselves
> e.g. `data instance D [a] :: * -> * = ...`
> Here the "header" is the bit before the "=" sign
What's weird is that you cannot actually compile code that this example
suggests is valid. Consider this:
{{{
{-# language TypeFamilies #-}
module BadSig where
data family Bar a :: *
data instance Bar Int :: * = Bool
}}}
It fails on GHC 8.6.2 with:
{{{
bad_sig.hs:6:28: error:
parse error on input ‘=’
Perhaps you need a 'let' in a 'do' block?
e.g. 'let x = 5' instead of 'x = 5'
|
6 | data instance Bar Int :: * = Bool
| ^
}}}
Oddly, GHC will accept the instance if the body is missing:
{{{
{-# language TypeFamilies #-}
module BadSig where
data family Bar a :: *
data instance Bar Int :: *
}}}
It is not clear to me whether or not this one should be accepted, but that
is beside the point. The first example should certainly be accepted. It
should also be accepted with `TYPE 'LiftedRep` instead of `*`, but it
fails with the same parser error when given that kind signature as well.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16024>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list