Haskell Core Libraries (haskell-src package)ParentContentsIndex
Language.Haskell.Pretty
Portability portable
Stability experimental
Maintainer libraries@haskell.org
Contents
Pretty printing
Pretty-printing styles (from Text.PrettyPrint.HughesPJ)
Haskell formatting modes
Description
Pretty printer for Haskell.
Synopsis
class Pretty a
prettyPrintStyleMode :: (Pretty a) => Style -> PPHsMode -> a -> String
prettyPrintWithMode :: (Pretty a) => PPHsMode -> a -> String
prettyPrint :: (Pretty a) => a -> String
data PPHsMode = PPHsMode {
classIndent :: Indent
doIndent :: Indent
caseIndent :: Indent
letIndent :: Indent
whereIndent :: Indent
onsideIndent :: Indent
spacing :: Bool
layout :: PPLayout
linePragmas :: Bool
comments :: Bool
}
type Indent = Int
data PPLayout
= PPOffsideRule
| PPSemiColon
| PPInLine
| PPNoLayout
defaultMode :: PPHsMode
Pretty printing
class Pretty a
Things that can be pretty-printed, including all the syntactic objects in Language.Haskell.Syntax.
Instances
Pretty HsModule
Pretty Module
Pretty HsExportSpec
Pretty HsImportDecl
Pretty HsImportSpec
Pretty HsDecl
Pretty HsAssoc
Pretty HsMatch
Pretty HsConDecl
Pretty HsBangType
Pretty HsQualType
Pretty HsType
Pretty HsRhs
Pretty HsGuardedRhs
Pretty HsLiteral
Pretty HsExp
Pretty HsPat
Pretty HsPatField
Pretty HsAlt
Pretty HsGuardedAlts
Pretty HsGuardedAlt
Pretty HsStmt
Pretty HsFieldUpdate
Pretty HsQOp
Pretty HsQName
Pretty HsOp
Pretty HsName
Pretty HsCName
prettyPrintStyleMode :: (Pretty a) => Style -> PPHsMode -> a -> String
pretty-print with a given style and mode.
prettyPrintWithMode :: (Pretty a) => PPHsMode -> a -> String
pretty-print with the default style and a given mode.
prettyPrint :: (Pretty a) => a -> String
pretty-print with the default style and defaultMode.
Pretty-printing styles (from Text.PrettyPrint.HughesPJ)
Haskell formatting modes
data PPHsMode
Pretty-printing parameters.
Constructors
PPHsMode
classIndent :: Indent indentation of a class or instance
doIndent :: Indent indentation of a do-expression
caseIndent :: Indent indentation of the body of a case expression
letIndent :: Indent indentation of the declarations in a let expression
whereIndent :: Indent indentation of the declarations in a where clause
onsideIndent :: Indent indentation added for continuation lines that would otherwise be offside
spacing :: Bool blank lines between statements?
layout :: PPLayout Pretty-printing style to use
linePragmas :: Bool add GHC-style LINE pragmas to output?
comments :: Bool not implemented yet
type Indent = Int
data PPLayout
Varieties of layout we can use.
Constructors
PPOffsideRule classical layout
PPSemiColon classical layout made explicit
PPInLine inline decls, with newlines between them
PPNoLayout everything on a single line
Instances
Eq PPLayout
defaultMode :: PPHsMode
The default mode: pretty-print using the offside rule and sensible defaults.
Produced by Haddock version 0.4