[Haskell-cafe] TemplateHaskell forces manual declaration ordering?

Michael Alan Dorman mdorman at ironicdesign.com
Tue May 20 10:43:12 UTC 2014


Hey, all,

While refactoring some code, I moved a newtype declaration, and suddenly
the compiler (up-to-date ghc-7.6.3 on Debian) started complaining that
it wasn't in scope when I attempted to use it in an ADT.

I'm still new to Haskell, so I assumed it was my misunderstanding, and
looked for documentation of declaration ordering constraints and
couldn't find any.  So then I went to make a toy case to demonstrate the
problem, and it worked:

    data Baz = Baz { foo :: Foo, bar :: !(Maybe Bar) }
    newtype Foo = Foo String
    newtype Bar = Bar String

So I started looking at the differences between that and my real code,
and the only thing that seemed at all signficant was that I was using TH
to generate some lenses.  And sure enough, adding that caused it to
fail:

    {-# LANGUAGE TemplateHaskell #-}
    import Control.Lens
    data Baz = Baz { foo :: Foo, bar :: !(Maybe Bar) }
    makeLenses ''Baz
    newtype Foo = Foo String
    newtype Bar = Bar String

If you feed this to ghci, you now get:

    test.hs:3:25: Not in scope: type constructor or class `Foo'

    test.hs:3:45:
        Not in scope: type constructor or class `Bar'
        Perhaps you meant `Baz' (line 3)

Wondering if lens was somehow doing something so exotic it was breaking
things, I tried aeson's TH support instead:

    {-# LANGUAGE TemplateHaskell #-}
    import Data.Aeson
    data Baz = Baz { foo :: Foo, bar :: !(Maybe Bar) }
    deriveJSON defaultOptions ''Baz
    newtype Foo = Foo String
    newtype Bar = Bar String

Exact same error.

That said, if I move the splices to the end of the file, everything
works:

    {-# LANGUAGE TemplateHaskell #-}
    import Data.Aeson
    data Baz = Baz { foo :: Foo, bar :: !(Maybe Bar) }
    newtype Foo = Foo String
    newtype Bar = Bar String
    deriveJSON defaultOptions ''Baz

I looked at the GHC docs on TH, and read the wiki page, and didn't see
anything suggesting that this was a known limitation, nor did I see a
bug in the known bug list that seemed pertinent.

So, I'm wondering if I've found an actual bug, or a known limitation
whose documentation should be made more prominent (since it seems to me
that it has pretty dramatic implications for program structure), or
what?  And is there any way around it other than moving all the splices
to the end of the source file?

Mike.


More information about the Haskell-Cafe mailing list