
#9813: Error when reifying type constructor -------------------------------------+------------------------------------- Reporter: owst | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1899 Wiki Page: | -------------------------------------+------------------------------------- Comment (by owst): Replying to [comment:33 simonpj]:
That does look feasible, since the code you are running in the splice all comes from other modules.
Do you have a compelling use-case? Most of the debate here is about mechanism.
My original report was modified from a program (https://github.com/owst/Penrose/blob/master/Main.hs#L139) where I do some rudimentary commandline option parsing using a deriving Read instance. To generate the usage of the program, I map over my Option type's constructors and show each one. Something along the lines of: {{{#!hs {-# LANGUAGE TemplateHaskell #-} import System.Environment ( getArgs, getProgName ) import Data.List ( intercalate ) import Data.Either ( partitionEithers ) import Language.Haskell.TH data Option = Foo | Bar | Baz deriving (Read, Show) -- If the next non-comment line is commented this will not compile: -- opts.hs:13:17: -- ‘Option’ is not in the type environment at a reify -- In the splice: -- $(do { ty <- reify ''Option; -- let showCon (NormalC n _) = ... -- showCon _ = ... -- ....; -- return . LitE . StringL $ intercalate ", " strs }) $(return []) allowedArgs :: String allowedArgs = $(do ty <- reify ''Option let showCon (NormalC n _) = nameBase n showCon _ = error "Can't handle non-normal constructors" strs = case ty of (TyConI (DataD _ _ _ cons _)) -> map showCon cons _ -> error "Can't handle non-tycon type" return . LitE . StringL $ intercalate ", " strs) main :: IO () main = do parsedArgs <- map parseArg `fmap` getArgs case partitionEithers parsedArgs of ([], okArgs) -> putStrLn $ "Computing with: " ++ show okArgs (badArgs, _) -> do progName <- getProgName putStrLn $ "Bad args: " ++ intercalate ", " badArgs putStrLn $ "Usage: " ++ progName ++ " " ++ allowedArgs where parseArg :: String -> Either String Option parseArg x = case reads x of [(o, "")] -> Right o _ -> Left $ show x }}} When I first wrote the program, I didn't need the `$(return [])` trick (using 7.6.3) and I was surprised that it broke upon upgrading to 7.8.3. In fact, I solved the problem by moving the declaration of `Option` to another module, but I still think it would be reasonable to allow it within the same declaration group, hence the proposed change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9813#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler