Hi cafe!

I'm hitting a very strange problem when using haskell-src-exts and haskell-src-exts-qq. Consider the following module:

\begin{code}
{-# Language QuasiQuotes #-}
module TestBug where

import Language.Haskell.Exts
import Language.Haskell.Exts.QQ

unit = TyTuple Boxed []

ty = [dec| quux :: (a,b) |]
\end{code}

This module doesn't load for me using ghc 7.0.3. I've pasted the full error message at the end of this email but the error message begins with the following lines:

TestBug.hs:11:11:
    Can't find interface-file declaration for variable Language.Haskell.Exts.Syntax.Boxed
      Probable cause: bug in .hi-boot file, or inconsistent .hi file
      Use -ddump-if-trace to get an idea of which file caused the error

Using -ddump-if-trace didn't help me much.

The funny thing is that if I comment out the last line (the definition of 'ty') then the module loads just fine even though it uses the Boxed type in the definition of 'unit'. So the problem only manifests itself when I use tuples from haskell-src-exts-qq. Everything else that I've used from haskell-src-exts-qq works fine, it's just when I try to use tuples that things go haywire.

I've tried to remove the packages and reinstall them but it didn't help.

Any clues?

Josef

TestBug.hs:11:11:
    Can't find interface-file declaration for variable Language.Haskell.Exts.Syntax.Boxed
      Probable cause: bug in .hi-boot file, or inconsistent .hi file
      Use -ddump-if-trace to get an idea of which file caused the error
    In the first argument of `Language.Haskell.Exts.Syntax.TyTuple', namely
      `Language.Haskell.Exts.Syntax.Boxed'
    In the third argument of `Language.Haskell.Exts.Syntax.TypeSig', namely
      `Language.Haskell.Exts.Syntax.TyTuple
         Language.Haskell.Exts.Syntax.Boxed
         ((:)
            (Language.Haskell.Exts.Syntax.TyVar
               (Language.Haskell.Exts.Syntax.Ident ((:) 'a' [])))
            ((:)
               (Language.Haskell.Exts.Syntax.TyVar
                  (Language.Haskell.Exts.Syntax.Ident ((:) 'b' [])))
               []))'
    In the expression:
      Language.Haskell.Exts.Syntax.TypeSig
        (SrcLoc
           ((:)
              '<'
              ((:)
                 'u'
                 ((:)
                    'n'
                    ((:)
                       'k'
                       ((:)
                          'n'
                          ((:)
                             'o'
                             ((:)
                                'w' ((:) 'n' ((:) '>' ((:) '.' ((:) 'h' ((:) 's' []))))))))))))
           1
           2)
        ((:)
           (Language.Haskell.Exts.Syntax.Ident
              ((:) 'q' ((:) 'u' ((:) 'u' ((:) 'x' [])))))
           [])
        (Language.Haskell.Exts.Syntax.TyTuple
           Language.Haskell.Exts.Syntax.Boxed
           ((:)
              (Language.Haskell.Exts.Syntax.TyVar
                 (Language.Haskell.Exts.Syntax.Ident ((:) 'a' [])))
              ((:)
                 (Language.Haskell.Exts.Syntax.TyVar
                    (Language.Haskell.Exts.Syntax.Ident ((:) 'b' [])))
                 [])))
Failed, modules loaded: none.