pretty newby

Per Larsson per at L4i.se
Tue Sep 23 18:25:05 EDT 2003


On Tuesday 23 September 2003 16.05, Luc Taesch wrote:
> are there any facility to pretty print an haskell program ?
> im aware of HPJ combinators library, but i was looking for a command line
> utility, rather.. am i missing an entry in HPJ ?
>
> thanks
> Luc
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell

Hi,
In GHC (and HUGS?) you can use the 'haskell-src' package which contains
functions for parsing and pretty-printing haskell code. Using these, it only 
takes a couple of lines to make your own command line, pretty-printer for 
haskell code. If you want to, you can use my implementation which I attach to 
this mail. The problem with the parser, however, is that it doesn't handle 
comments at all.

Regards
Per-------------- next part --------------
-- FILE: HsIndent.hs
-- AUTH: Per Larsson
-- DATE: 03/10/2003
-- CODE: Haskell Code

module Main where

import System.Environment
import System.Exit
import System.IO
import Control.Monad
import Language.Haskell.Parser
import Language.Haskell.Pretty
import System.Console.GetOpt

header  = "hsindent [OPTION ...] FILE"
version = "hsindent 1.0"
usage   = usageInfo header options

data Config = Config {showHelp, showVersion :: Bool, pmode :: PPHsMode}
 
defaultConfig = Config False False defaultStyle

defaultStyle :: PPHsMode
defaultStyle = PPHsMode { 
    classIndent = 8,
    doIndent = 3,
    caseIndent = 5,
    letIndent = 4,
    whereIndent = 6,
    onsideIndent = 2,
    spacing = True,
    layout = PPOffsideRule,
    linePragmas = False,
    comments = True
  }

options :: [OptDescr (Config -> Config)]
options = 
    [ opt 'h' "help" "print this help information and exit" 
      (\c -> c {showHelp = True}) 
    , opt 'v' "version" "print version information and exit"
      (\c -> c {showVersion = True})
    , opt 'u' "nospacing" "don't insert blank lines"
      (\c -> c {pmode = (pmode c) {spacing = False}})
    , opt 'p' "pragmas"  "insert source pragmas" 
      (\c -> c {pmode = (pmode c) {linePragmas = True}})
    , opt 'e' "comments"  "keep comments" 
      (\c -> c {pmode = (pmode c) {comments = True}}) 
    , arg 's' "class" "N" "indent class declarations N columns" 
      (\s c -> c {pmode = (pmode c) {classIndent = read s}})
    , arg 'd' "do" "N" "indent do expressions N columns"
      (\s c -> c {pmode = (pmode c) {doIndent = read s}}) 
    , arg 'w' "where" "N" "indent where expressions N columns" 
      (\s c -> c {pmode = (pmode c) {whereIndent = read s}})
    , arg 'l' "let" "N" "indent let expressions N columns"
      (\s c -> c {pmode = (pmode c) {letIndent = read s}})
    , arg 'c' "case" "N" "indent case expressions N columns" 
      (\s c -> c {pmode = (pmode c) {caseIndent = read s}})
    , arg 'o' "onside" "N" "indent at line continuations N columns" 
      (\s c -> c {pmode = (pmode c) {onsideIndent = read s}})
    , arg 'y' "layout"  "ARG" "set layout style to ARG, one of\n\
	      \ 'OffsideRule', 'SemiColon', 'Inline' or 'NoLayout'"
      (\s c -> c {pmode = (pmode c) {layout = toLayout s}})  
    ] 
   where
   opt short long msg update = 
       Option [short] [long] (NoArg update) msg
   arg short long argdescr msg update = 
       Option [short] [long] (ReqArg update argdescr) msg
  
toLayout :: String -> PPLayout
toLayout "OffsideRule" = PPOffsideRule
toLayout "SemiColon"   = PPSemiColon
toLayout "InLine"      = PPInLine
toLayout "NoLayout"    = PPNoLayout
toLayout _             = error "toLayout"

--------------------------------------------------------------------------   

main = do 
    args <- getArgs
    (conf,files) <- case getOpt Permute options args of
	(o,n,[])   -> return (foldr ($) defaultConfig o, n)
	(_,_,errs) -> error (concat errs ++ usageInfo header options) 
    when (showHelp conf) (exitSuccess usage)
    when (showVersion conf) (exitSuccess version)
    unless (length files == 1) (exitFail usage)
    file <- return (head files)
    h <- openFile file ReadMode
    s <- hGetContents h
    result <- return (parseModuleWithMode (ParseMode file) s)
    case result of
        ParseOk hsModule -> 
	    exitSuccess (prettyPrintWithMode (pmode conf) hsModule)
	ParseFailed pos msg -> 
            exitFail ("Parse Error at: " ++ show pos ++ "\n " ++ show msg)
    where 
    exitSuccess msg = (putStrLn msg >> exitWith ExitSuccess)
    exitFail msg = (putStrLn msg >> exitFailure)
 




More information about the Haskell mailing list