Template Haskell seems to be type-checking some quasi-quotes, even when they
are not going to be used.  This is of course a terrible nuisance, since it
means it can't be used to work around interface incompatibilities between
libraries for different versions of GHC (such as the recent change in
RegexString.matchRegexAll's type).  Maybe I will have to go back to using
cpp ...

For example, the attached file fails to compile.


# ghc TestSplice.hs -c -fglasgow-exts > > TestSplice.hs:7: > Couldn't match `f a' against `Bool' > Expected type: f a > Inferred type: Bool > In the second argument of `fmap', namely `True' > In the definition of `TestSplice.p': TestSplice.p = fmap id True

This occurs for both ghc 6.0.1 and the recent snapshot 6.3.20031201



Another problem is that Template Haskell objects to undefined variables in
unused splices.  Thus if I replace "p = fmap id True" in the
attached file by "foo = bar", I get "TestSplice2.hs:7: Variable not in scope: `bar'"

module TestSplice where

$(
   if False
      then
         [d|
            p = fmap id True
         |]
      else
         [d|
            d = 2
         |]
   )
module TestSplice where

$(
   if False
      then
         [d|
            foo = bar
         |]
      else
         [d|
            d = 2
         |]
   )
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to