
#9022: TH pretty printer and GHC parser semicolon placement mismatch ----------------------------+---------------------------------------------- Reporter: roldugin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 (Parser) | Operating System: Unknown/Multiple Keywords: | Type of failure: GHC rejects valid program Architecture: | Test Case: Unknown/Multiple | Blocking: Difficulty: Unknown | Blocked By: | Related Tickets: | ----------------------------+---------------------------------------------- In GHC 7.8 TemplateHaskell pretty printer started inserting explicit braces and semicolons. It puts semicolons at the end of the line as opposed to the beginning of the next line. This causes GHC to fail parsing if we try to compile the pretty printed code. {{{ $ cat Foo.hs module Main where import Language.Haskell.TH main = putStrLn $ pprint foo foo :: Dec foo = barD where barD = FunD ( mkName "bar" ) [ Clause manyArgs (NormalB barBody) [] ] barBody = DoE [letxStmt, retxStmt] letxStmt = LetS [ ValD (VarP xName) (NormalB $ LitE $ IntegerL 5) [] ] retxStmt = NoBindS $ AppE returnVarE xVarE xName = mkName "x" returnVarE = VarE $ mkName "return" xVarE = VarE xName manyArgs = map argP [0..9] argP n = VarP $ mkName $ "arg" ++ show n $ ghc-7.8.2 Foo.hs [1 of 1] Compiling Main ( Foo.hs, Foo.o ) Linking Foo ... $ ./Foo | tee Bar.hs bar arg0 arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 = do {let x = 5; return x} $ ghc Bar.hs [1 of 1] Compiling Main ( Bar.hs, Bar.o ) Bar.hs:2:61: parse error on input `return' }}} I don't know if this is a problem with TH pretty printer or if GHC is supposed to parse semicolons wherever they are.. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9022 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler