Fwd: Generating valid Haskell code using the GHC API pretty
printer
Christian Maeder
Christian.Maeder at dfki.de
Wed Jul 22 10:33:47 EDT 2009
Thomas Schilling wrote:
> Forgot to include the list.
>
> ---------- Forwarded message ----------
> From: Thomas Schilling <nominolo at googlemail.com>
> Date: 2009/7/22
> Subject: Re: Generating valid Haskell code using the GHC API pretty printer
> To: Jan Schaumlöffel <jsch at informatik.uni-kiel.de>
>
>
> The pretty printer never prints { .. } for a do expression. You can
> control which things are printed unqualified by setting the
> "PrintUnqualified" part properly. The most straightforward way is to
> use GHC.mkPrintUnqualifiedForModule which only prints things qualified
> that are not imported in the given module. See 'withPprStyle' and
> 'mkUserStyle' in Outputable.
>
> That said, if you're trying to do source-to-source transformations you
> probably want to keep the original layout as much as possible. GHC's
> pretty-printer isn't designed for that. GHC's syntax tree has very
> accurate source locations, so you could start from there and build
> your own pretty printer.
I believe, Language.Haskell.Pretty can properly output haskell code (and
the GHC API should be able to do so, too. Does the GHC API output tabs?)
Below is a snippet for parsing and printing only.
Cheers Christian
import Language.Haskell.Pretty as HP
import Language.Haskell.Syntax
import Language.Haskell.Parser
import System.Environment
processFile :: String -> IO ()
processFile file = do
src <- readFile file
case parseModuleWithMode (ParseMode file) src of
ParseOk hsMod -> putStrLn $ HP.prettyPrint hsMod
ParseFailed loc err -> fail $
err ++ " in '" ++ file ++ "' line " ++ show (srcLine loc)
main :: IO ()
main = do
args <- getArgs
mapM_ processFile args
More information about the Glasgow-haskell-users
mailing list