[GHC] #10384: "Can't splice the polymorphic local variable" check looks dead
GHC
ghc-devs at haskell.org
Tue May 5 17:30:40 UTC 2015
#10384: "Can't splice the polymorphic local variable" check looks dead
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner: ezyang
Type: task | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Changes (by ezyang):
* owner: => ezyang
Comment:
Looking at the Core of:
{{{
{-# LANGUAGE TemplateHaskell, FlexibleInstances, IncoherentInstances #-}
module A where
import Language.Haskell.TH.Syntax
instance Lift a where
lift = undefined
x = \y -> [|| y ||]
}}}
we can see that it goes through `Lift`, and then an `unsafeTExpCoerce`, so
there's no need for a separate `tlift` typeclass. (`tcTypedBracket` is
responsible for typechecking the expression and then coercing it.)
But that was enough of a hint to let me figure out how to tickle this
case.
{{{
{-# LANGUAGE TemplateHaskell, RankNTypes, ScopedTypeVariables #-}
module A where
x = \(y :: forall a. a -> a) -> [|| y ||]
}}}
{{{
A.hs:3:37:
Can't splice the polymorphic local variable ‘y’
In the Template Haskell quotation [|| y ||]
In the expression: [|| y ||]
In the expression: \ (y :: forall a. a -> a) -> [|| y ||]
}}}
I'll add a test-case for it.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10384#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list