[GHC] #10384: "Can't splice the polymorphic local variable" check looks dead

GHC ghc-devs at haskell.org
Tue May 5 03:14:45 UTC 2015


#10384: "Can't splice the polymorphic local variable" check looks dead
-------------------------------------+-------------------------------------
              Reporter:  ezyang      |             Owner:
                  Type:  task        |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Template    |           Version:  7.11
  Haskell                            |  Operating System:  Unknown/Multiple
              Keywords:              |   Type of failure:  None/Unknown
          Architecture:              |        Blocked By:
  Unknown/Multiple                   |   Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 While I was looking for TH checks which might want to be checked when
 `Quotes` are enabled ala #10382, I found the "Can't splice the polymorphic
 local variable" check in `checkCrossStageLifting` in `TcExpr`. I thought
 this was a bit odd, because there is another implementation of this very
 function in `RnSplice`.

 So I went ahead and removed this check from the compiler, and it validated
 fine.

 I then went and tried to see if I could tickle the problem. An old mailing
 list suggested the following test program to induce the error:

 {{{
 module TH_polymorphic where

 import Language.Haskell.TH
 import Language.Haskell.TH.Syntax

 -- See https://mail.haskell.org/pipermail/template-
 haskell/2006-April/000552.html

 test2 () = runQ [| foldr f z xs |]
     where (f,z,xs) = undefined
 }}}

 but I get this error:

 {{{
 TH_polymorphic.hs:8:17: error:
     Could not deduce (Lift t0) arising from a use of ‘lift’
     from the context: Quasi m
       bound by the inferred type of test2 :: Quasi m => () -> m Exp
       at TH_polymorphic.hs:(8,1)-(9,30)
     The type variable ‘t0’ is ambiguous
     Note: there are several potential instances:
       instance (Lift a, Lift b) => Lift (Either a b)
         -- Defined in ‘Language.Haskell.TH.Syntax’
       instance Lift a => Lift (Maybe a)
         -- Defined in ‘Language.Haskell.TH.Syntax’
       instance Lift Int16 -- Defined in ‘Language.Haskell.TH.Syntax’
       ...plus 24 others
     In the expression: lift xs
     In the first argument of ‘runQ’, namely
       ‘[| foldr f z xs |]
        pending(rn) [<xs, lift xs>, <z, lift z>, <f, lift f>]’
     In the expression:
       runQ
         [| foldr f z xs |]
         pending(rn) [<xs, lift xs>, <z, lift z>, <f, lift f>]
 }}}

 which seems to be induced the check in `RnSplice`.

 So is it dead? If so, let's remove it!

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10384>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list