I've fixed GHC's pretty-printer to print do-notation using braces and semi-colons, which is much more robust. I hope that's useful
SImon | -----Original Message----- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Jan Schaumlöffel | Sent: 22 July 2009 14:28 | To: glasgow-haskell-users@haskell.org | Subject: Generating valid Haskell code using the GHC API pretty printer | | Hello everyone, | | we are trying to use the GHC API for a source-to-source transformation | on Haskell programs. The result of parsing and typechecking a module | enables us to apply the transformation, but writing the transformed | module back using the pretty printer (Outputable) generates invalid | Haskell code. | | For one thing, since even the names defined in the current module are | fully qualified, the resulting code is not valid anymore. | | This can be worked around, but there is another issue: Simply reading | the following program and then writing it out using the pretty printer | renders the resulting code invalid. | | > module Main where | > main = do | > if True then putStrLn "longlonglonglonglonglongline" | > else return () | > longlonglonglonglonglonglonglonglonglonglonglongname $ "test" | > longlonglonglonglonglonglonglonglonglonglonglongname = putStrLn | | The result looks like this: | | > Main.main = do if GHC.Bool.True then | > System.IO.putStrLn "longlonglonglonglonglongline" | > else | > GHC.Base.return () | > Main.longlonglonglonglonglonglonglonglonglonglonglongname | > GHC.Base.$ | > "test" | > Main.longlonglonglonglonglonglonglonglonglonglonglongname = System.IO.putStrLn | | There are two different problems in this output: | | 1) the indentation of "if ... then ... else" violates the "do"-block | layout rule | 2) the indentation of the long function call is invalid | | It looks like those problems could be avoided if the pretty printer | could be configured to consistently use "do { ... ; ... }" notation, | but we have been unable to figure out how. Is there a canonical way | to use the GHC API to pretty print to valid Haskell code? | | Kind regards, | Jan | | Appended is our current code to execute the transformation above (the | module to be read is expected in a file "dummy.hs" for simplicity). | Please excuse if this might not be a minimal example. | | module Main where | | import GHC | import GHC.Paths | import Outputable | | main = do | x <- runGhc (Just libdir) $ do | dflags <- getSessionDynFlags | setSessionDynFlags (dflags { hscTarget = HscNothing, | ghcLink = NoLink }) | | target <- guessTarget "dummy.hs" Nothing | setTargets [target] | load LoadAllTargets | | graph <- getModuleGraph | let unparsedmod = head graph | | parsedmod <- parseModule unparsedmod | typecheckedmod <- typecheckModule parsedmod | let Just renamedsource = renamedSource typecheckedmod | (group,_,_,_,_) = renamedsource | moduledings = (ms_mod unparsedmod) | | return (showSDoc (ppr group)) | putStr $ x ++ "\n" | | -- | If you're happy and you know it, syntax error! _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users