[Template-haskell] Dyamic scoping question

Bryn Keller xoltar at xoltar.org
Mon Oct 25 14:47:40 EDT 2004


Hi folks,

I'm trying to use TH to generate parsers and writers for arbitrary 
datatypes. In the end I'd like every part of the declaration and 
generation of these functions to be automatic, but at this early stage 
I'm just trying to get one aspect of all that to work. So at the moment, 
all I want is to generate a function that exercises a parsing 
computation I've already defined earlier in the module:

import Text.ParserCombinators.Parsec

import Splices

data SomeType = S Int

sometype_p = do {string "S"; num <- many1 digit; return $ S (read num)}

readSomeType = $(reifyDecl SomeType >>= mkLineReader)


and in Splices.hs:

module Splices where

import Language.Haskell.THSyntax
import Text.ParserCombinators.Parsec (parse)
import Data.Char (toLower)

modifyName f name = concat [modules, ":", f origName]
  where
   (modules, (_:origName)) = break (==':') name
  
lower = map toLower

mkLineReader :: Dec -> Q Exp
mkLineReader (DataD _ name _ fields _) = do
    let parserName = varE $ modifyName ((++"_p").lower) name
    [|
     \line -> case parse $(parserName) line line of
                        Left err -> error (show err)
            Right val -> val
     |]

Now, when I try to compile this I get a message like so:

tcLookup: `sometype_p' is not in scope
In the first argument of `parse', namely `sometype_p'
In the scrutinee of a case expression:
    parse sometype_p line'0 line'0
In the case expression:
    case parse sometype_p line'0 line'0 of
      Left err'1 -> error (show err'1)
      Right val'2 -> val'2

When I add -ddump-splices, it prints this in addition:

   \ line'0
       -> case
              Text.ParserCombinators.Parsec.Prim.parse Main.sometype_p
                                                       line'0
                                                       line'0
          of
            Data.Either.Left err'1 -> GHC.Err.error (GHC.Show.show err'1)
            Data.Either.Right val'2 -> val'2

which tells me that the name sometype_p is getting built correctly, but 
it's just not finding the sometype_p that I've already defined. I 
thought that varE was the way to capture existing variables of this sort 
in Template Haskell, was I mistaken? What is the approved way? Or have I 
just missed something crucial?

Thanks,

Bryn


More information about the template-haskell mailing list