Improve error message for misplaced quote inside promoted qualified type
The program
{-# LANGUAGE DataKinds #-}
module Foo where
import Data.Proxy
data MyNat = Z | S MyNat
bar :: Proxy Foo.'Z -> Int
bar _ = 0
fails with the error
Foo.hs:7:17:
Illegal symbol '.' in type
Perhaps you intended to use RankNTypes or a similar language
extension to enable explicit-forall syntax: forall <tvs>. <type>
Failed, modules loaded: none.
I believe the program above should compile without error. In the example above, I could make the code compile with my intended meanign using Z
, 'Z
, or even Foo.Z
in place of Foo.'Z
, all of which refer to Foo.'Z
. However, if there is also a vanilla type Z
in scope and another promoted constructor 'Z
in scope, I have no way to disambiguate the reference to 'Z
in bar
:
Z
andFoo.Z
refer to the vanilla type'Z
could be from the promotedMyNat
constructor, or from the other module
Concretely, I could import Data.Type.Natural
from type-natural, which also defines the promoted constructor 'Z
.
{-# LANGUAGE DataKinds #-}
module Foo where
import Data.Proxy
import Data.Type.Natural
data MyNat = Z | S MyNat
bar :: Proxy Foo.'Z -> Int
bar _ = 0
In this case, there is no way for me to indicate that bar
has the type Foo.'Z -> Int
.
Although a user cannot define the a type beginning with a tick, they are perfectly valid types to refer to. I suspect the parser is failing to make this distinction, at least in the context of name qualification.
As a side note, if I do as the error suggests and useRankNTypes
, I get the same error message. It's a bit strange for GHC suggest adding an extension that is already enabled.