[GHC] #15833: Typed template haskell quote fails to typecheck when spliced due to an ambiguous type variable

GHC ghc-devs at haskell.org
Tue Oct 30 11:33:39 UTC 2018


#15833: Typed template haskell quote fails to typecheck when spliced due to an
ambiguous type variable
-------------------------------------+-------------------------------------
        Reporter:  mpickering        |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.6.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by mpickering):

 Here is a minimised version which still exhibits the same failure.

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeApplications #-}
 {-# OPTIONS_GHC -Wall #-}
 module Compiler where

 import Language.Haskell.TH

 type QTExp a = Q (TExp a)

 fix :: (a -> a) -> a
 fix f = let x = f x in x

 while ::
   Monoid m =>
   QTExp (IO m -> IO m) -> QTExp (IO m)
 while b = [|| fix (\r -> whenM ($$b r)) ||]

 whenM :: Monoid m => a ->  m
 whenM _ = mempty

 execOp :: forall m . Monoid m => QTExp (IO m)
 execOp = while [|| \r -> $$(while @m [|| id ||]) >> r ||]

 runQuery :: QTExp (IO ())
 runQuery = execOp
 }}}

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


More information about the ghc-tickets mailing list