#4125: Template haskell rejects duplicate instances before they're spliced
----------------------------------------+-----------------------------------
Reporter: lilac | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Template Haskell | Version: 6.12.1
Resolution: invalid | Keywords:
Difficulty: | Os: Unknown/Multiple
Testcase: | Architecture: Unknown/Multiple
Failure: GHC rejects valid program |
----------------------------------------+-----------------------------------
Comment(by lilac):
> Your example contains an instance declaration. If you saw
> {{{[| return True :: T Bool |]}}} you'd probably expect that
> to typecheck if (and only if) T is an instance of Monad.
Actually, no, and I think that's the essence of the problem. I think the
feature I want is to turn off all typechecking within TH quotations (or,
more accurately, to defer all such checking until the quotation is
actually spliced). I have a few arguments in favour of this change:
Firstly, suppose today I write:
{{{
module Main where
data T a = T
[d|instance Monad T where return _ = T; T >>= f = T|]
[d|foo = return True :: T Bool|]
}}}
If I now refactor this:
{{{
module Main where
import Control.Monad
data T a = T
liftM2 (++) [d|instance Monad T where return _ = T; T >>= f = T|] [d|foo =
return True :: T Bool|]
}}}
... it would fail to compile. Result: TH code is not composable.
As it happens, I've committed some intellectual fraud above: {{{[| return
True :: T Bool |]}}} is accepted by GHC 6.12.1 whether or not a Monad T
instance is in scope. And that's my second argument: as it stands, it is
very unclear what code will be accepted and what code will not; the only
way to know seems to be to try it on the versions of GHC you care about.
If I used the second code fragment above, would I run the risk that it'd
be broken in later versions of GHC with "better" typechecking?
My third argument is: the purpose of static types is to reject incorrect
programs (while minimizing the number of correct programs rejected). It
seems to me that typechecking TH prior to the splice point can only reject
correct programs (any incorrect program would be rejected anyway by post-
splice typechecking).
Is the above anywhere near convincing enough for it to be worth opening a
feature request?
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4125#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs