RE: [Template-haskell] Dyamic scoping question
Here's your program boiled down a bit foo = 3 baz = $(varE ("fo" ++ "o")) Like any Haskell compiler, GHC does dependency analysis, and type-checks in that order. There no way for it to see that 'baz' depends on 'foo', so it may well typecheck the definition of baz before that of foo. I haven't actually run your example, but I bet that's what's happening. "-ddump-rn" would tell you, because it shows the code after dependency analysis. I wonder if others have tripped over this. There is a tension between dynamic scope and dependency analysis (which is required for type checking) that's hard to resolve. For example, you probably want the example to work even if the definition of 'foo' is after that of 'baz'; at least that's the standard Haskell story. I suppose a workaround is to put 'foo' in another module, but it's not nice. Simon | -----Original Message----- | From: template-haskell-bounces@haskell.org [mailto:template-haskell-bounces@haskell.org] On | Behalf Of Bryn Keller | Sent: 25 October 2004 19:48 | To: template-haskell@haskell.org | Subject: [Template-haskell] Dyamic scoping question | | 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 | _______________________________________________ | template-haskell mailing list | template-haskell@haskell.org | http://www.haskell.org/mailman/listinfo/template-haskell
Simon Peyton-Jones wrote:
Here's your program boiled down a bit foo = 3 baz = $(varE ("fo" ++ "o"))
Like any Haskell compiler, GHC does dependency analysis, and type-checks in that order. There no way for it to see that 'baz' depends on 'foo', so it may well typecheck the definition of baz before that of foo. I haven't actually run your example, but I bet that's what's happening. "-ddump-rn" would tell you, because it shows the code after dependency analysis.
Ah, thanks, that makes a lot of sense. In fact, -ddump-rn reveals that's exactly what's happening.
I wonder if others have tripped over this. There is a tension between dynamic scope and dependency analysis (which is required for type checking) that's hard to resolve. For example, you probably want the example to work even if the definition of 'foo' is after that of 'baz'; at least that's the standard Haskell story.
I suppose a workaround is to put 'foo' in another module, but it's not nice.
I just rephrased the code in such a way that I didn't need that dynamic scoping anymore. I don't think using modules to constrain dependency analysis for TH is such a bad idea, though. Particularly if there were some syntax for creating said modules in the same file... That's a discussion for another day, though. Thanks for the help! Bryn
participants (2)
-
Bryn Keller -
Simon Peyton-Jones