[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 10:20:29 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
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 It should be the case that a code value constructed using typed template
 haskell should never fail to type check when spliced. Running `ghc
 Test.hs` with the following two modules produces an error about an
 ambiguous type variable.

 https://gist.github.com/5890c14dda73da738d2041c7f677b786


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

 import Language.Haskell.TH

 data Operator = Scan
               | Join Operator Operator deriving Show

 queryJoin :: Operator
 queryJoin = Join Scan Scan

 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 True ($$b r)) ||]

 whenM :: Monoid m => Bool -> m -> m
 whenM b act = if b then act else mempty

 execOp :: Monoid m => Operator -> QTExp (IO m) -> QTExp (IO m)
 execOp op yld =
   case op of
     Scan ->
       while [|| \r -> ($$(yld) >> r)||]
     Join left right ->
       execOp left (execOp right yld)

 runQuery :: QTExp (IO ())
 runQuery = execOp (Join Scan Scan) ([|| return () ||])
 }}}

 {{{

 {-# LANGUAGE TemplateHaskell #-}
 {-# OPTIONS_GHC -ddump-splices #-}
 module Test where

 import qualified Compiler as C

 main :: IO ()
 main = do
 $$(C.runQuery)

 }}}

 {{{
 Test.hs:9:6: error:
     • Ambiguous type variable ‘a0’ arising from a use of ‘C.whenM’
       prevents the constraint ‘(Monoid a0)’ from being solved.
       Relevant bindings include r_a5GX :: IO a0 (bound at Test.hs:9:6)
       Probable fix: use a type annotation to specify what ‘a0’ should be.
       These potential instances exist:
         instance Monoid a => Monoid (IO a) -- Defined in ‘GHC.Base’
         instance Monoid Ordering -- Defined in ‘GHC.Base’
         instance Semigroup a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
         ...plus 7 others
         (use -fprint-potential-instances to see them all)
     • In the expression:
         (C.whenM True) ((\ r_a5GY -> ((return ()) >> r_a5GY)) r_a5GX)
       In the first argument of ‘C.fix’, namely
         ‘(\ r_a5GX
             -> (C.whenM True) ((\ r_a5GY -> ((return ()) >> r_a5GY))
 r_a5GX))’
       In the first argument of ‘(>>)’, namely
         ‘(C.fix
             (\ r_a5GX
                -> (C.whenM True) ((\ r_a5GY -> ((return ()) >> r_a5GY))
 r_a5GX)))’
   |
 9 |   $$(C.runQuery)
   |
 }}}

 The generated code

 {{{
 Test.hs:9:6-15: Splicing expression
     C.runQuery
   ======>
     C.fix
       (\ r_a5GV
          -> (C.whenM True)
               ((\ r_a5GW
                   -> ((C.fix
                          (\ r_a5GX
                             -> (C.whenM True)
                                  ((\ r_a5GY -> ((return GHC.Tuple.()) >>
 r_a5GY)) r_a5GX)))
                         >> r_a5GW))
                  r_a5GV))
 }}}

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


More information about the ghc-tickets mailing list