[GHC] #15321: Typed holes in Template Haskell splices produce bewildering error messages
GHC
ghc-devs at haskell.org
Thu Jun 28 15:49:36 UTC 2018
#15321: Typed holes in Template Haskell splices produce bewildering error messages
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Template | Version: 8.4.3
Haskell |
Keywords: TypedHoles | Operating System: Unknown/Multiple
Architecture: | Type of failure: Poor/confusing
Unknown/Multiple | error message
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
If you compile this program with GHC 8.4 or later:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module Bug where
foo :: String
foo = test
bar :: String
bar = $(_ "baz")
}}}
You'll be greeted with a rather strange error message:
{{{
$ /opt/ghc/8.4.3/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:8:7: error:
• GHC stage restriction:
‘foo’ is used in a top-level splice, quasi-quote, or annotation,
and must be imported, not defined locally
• In the untyped splice: $(_ "baz")
|
8 | bar = $(_ "baz")
| ^^^^^^^^^^
}}}
`foo` has nothing do with how `bar`'s RHS should be typechecked, so why is
it being mentioned in the error message?
In contrast, GHC 8.2 and earlier gives you quite a nice error message:
{{{
$ /opt/ghc/8.2.2/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:8:9: error:
• Found hole: _ :: [Char] -> Language.Haskell.TH.Lib.ExpQ
• In the expression: _
In the expression: _ "baz"
In the untyped splice: $(_ "baz")
|
8 | bar = $(_ "baz")
| ^
}}}
Tritlo, my hunch is that the valid hole fits stuff is the culprit here. Do
you think that perhaps when building the subsumption graph, we are trying
to check the hole's type against that of `foo`, which causes the stage
restriction error? If so, do you think it is possible to work around this?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15321>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list