haskell-src-exts-1.3.5: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printerSource codeContentsIndex
Language.Haskell.Exts.Pretty
Portabilityportable
Stabilitystable
MaintainerNiklas Broberg, d00nibro@chalmers.se
Contents
Pretty printing
Pretty-printing styles (from Text.PrettyPrint.HughesPJ)
Haskell formatting modes
Description
Pretty printer for Haskell with extensions.
Synopsis
class Pretty a
prettyPrintStyleMode :: Pretty a => Style -> PPHsMode -> a -> String
prettyPrintWithMode :: Pretty a => PPHsMode -> a -> String
prettyPrint :: Pretty a => a -> String
data Style = Style {
mode :: Mode
lineLength :: Int
ribbonsPerLine :: Float
}
style :: Style
data Mode
= PageMode
| ZigZagMode
| LeftMode
| OneLineMode
data PPHsMode = PPHsMode {
classIndent :: Indent
doIndent :: Indent
caseIndent :: Indent
letIndent :: Indent
whereIndent :: Indent
onsideIndent :: Indent
spacing :: Bool
layout :: PPLayout
linePragmas :: Bool
}
type Indent = Int
data PPLayout
= PPOffsideRule
| PPSemiColon
| PPInLine
| PPNoLayout
defaultMode :: PPHsMode
Pretty printing
class Pretty a Source
Things that can be pretty-printed, including all the syntactic objects in Language.Haskell.Exts.Syntax.
show/hide Instances
Pretty SrcSpan
Pretty SrcLoc
Pretty Tool
Pretty GuardedAlt
Pretty GuardedAlts
Pretty Alt
Pretty FieldUpdate
Pretty QualStmt
Pretty Stmt
Pretty PatField
Pretty RPat
Pretty RPatOp
Pretty PXAttr
Pretty Pat
Pretty RuleVar
Pretty Rule
Pretty Activation
Pretty OptionPragma
Pretty CallConv
Pretty Safety
Pretty Splice
Pretty Bracket
Pretty XAttr
Pretty XName
Pretty Exp
Pretty Literal
Pretty Asst
Pretty FunDep
Pretty Kind
Pretty TyVarBind
Pretty Type
Pretty GuardedRhs
Pretty Rhs
Pretty BangType
Pretty InstDecl
Pretty ClassDecl
Pretty GadtDecl
Pretty ConDecl
Pretty QualConDecl
Pretty Match
Pretty IPBind
Pretty DataOrNew
Pretty Decl
Pretty Assoc
Pretty ImportSpec
Pretty ImportDecl
Pretty ExportSpec
Pretty Module
Pretty CName
Pretty Op
Pretty QOp
Pretty IPName
Pretty Name
Pretty QName
Pretty SpecialCon
Pretty ModuleName
SrcInfo loc => Pretty (GuardedAlt loc)
SrcInfo loc => Pretty (GuardedAlts loc)
SrcInfo loc => Pretty (Alt loc)
SrcInfo loc => Pretty (FieldUpdate loc)
SrcInfo loc => Pretty (QualStmt loc)
SrcInfo loc => Pretty (Stmt loc)
SrcInfo loc => Pretty (PatField loc)
SrcInfo loc => Pretty (RPat loc)
Pretty (RPatOp l)
SrcInfo loc => Pretty (PXAttr loc)
SrcInfo loc => Pretty (Pat loc)
Pretty (WarningText l)
Pretty (RuleVar l)
SrcInfo loc => Pretty (Rule loc)
Pretty (Activation l)
Pretty (OptionPragma l)
Pretty (CallConv l)
Pretty (Safety l)
SrcInfo loc => Pretty (Splice loc)
SrcInfo loc => Pretty (Bracket loc)
SrcInfo loc => Pretty (XAttr loc)
Pretty (XName l)
SrcInfo loc => Pretty (Exp loc)
Pretty (Literal l)
Pretty (Asst l)
Pretty (Context l)
Pretty (FunDep l)
Pretty (Kind l)
Pretty (TyVarBind l)
Pretty (Type l)
SrcInfo loc => Pretty (GuardedRhs loc)
SrcInfo loc => Pretty (Rhs loc)
Pretty (BangType l)
SrcInfo loc => Pretty (InstDecl loc)
SrcInfo loc => Pretty (ClassDecl loc)
Pretty (GadtDecl l)
Pretty (FieldDecl l)
Pretty (ConDecl l)
Pretty (QualConDecl l)
SrcInfo pos => Pretty (Match pos)
SrcInfo loc => Pretty (IPBind loc)
Pretty (Deriving l)
Pretty (InstHead l)
Pretty (DeclHead l)
Pretty (DataOrNew l)
SrcInfo pos => Pretty (Decl pos)
Pretty (Assoc l)
Pretty (ImportSpec l)
Pretty (ImportSpecList l)
SrcInfo pos => Pretty (ImportDecl pos)
Pretty (ExportSpec l)
Pretty (ExportSpecList l)
Pretty (ModuleHead l)
SrcInfo pos => Pretty (Module pos)
Pretty (CName l)
Pretty (Op l)
Pretty (QOp l)
Pretty (IPName l)
Pretty (Name l)
Pretty (QName l)
Pretty (ModuleName l)
SrcInfo loc => Pretty (PAsst loc)
SrcInfo loc => Pretty (PType loc)
SrcInfo loc => Pretty (PContext loc)
SrcInfo loc => Pretty (ParseXAttr loc)
SrcInfo loc => Pretty (PFieldUpdate loc)
SrcInfo loc => Pretty (PExp loc)
prettyPrintStyleMode :: Pretty a => Style -> PPHsMode -> a -> StringSource
pretty-print with a given style and mode.
prettyPrintWithMode :: Pretty a => PPHsMode -> a -> StringSource
pretty-print with the default style and a given mode.
prettyPrint :: Pretty a => a -> StringSource
pretty-print with the default style and defaultMode.
Pretty-printing styles (from Text.PrettyPrint.HughesPJ)
data Style Source
A rendering style.
Constructors
Style
mode :: ModeThe rendering mode
lineLength :: IntLength of line, in chars
ribbonsPerLine :: FloatRatio of ribbon length to line length
style :: StyleSource
The default style (mode=PageMode, lineLength=100, ribbonsPerLine=1.5).
data Mode Source
Rendering mode.
Constructors
PageModeNormal
ZigZagModeWith zig-zag cuts
LeftModeNo indentation, infinitely long lines
OneLineModeAll on one line
Haskell formatting modes
data PPHsMode Source

Pretty-printing parameters.

Note: the onsideIndent must be positive and less than all other indents.

Constructors
PPHsMode
classIndent :: Indentindentation of a class or instance
doIndent :: Indentindentation of a do-expression
caseIndent :: Indentindentation of the body of a case expression
letIndent :: Indentindentation of the declarations in a let expression
whereIndent :: Indentindentation of the declarations in a where clause
onsideIndent :: Indentindentation added for continuation lines that would otherwise be offside
spacing :: Boolblank lines between statements?
layout :: PPLayoutPretty-printing style to use
linePragmas :: Booladd GHC-style LINE pragmas to output?
type Indent = IntSource
data PPLayout Source
Varieties of layout we can use.
Constructors
PPOffsideRuleclassical layout
PPSemiColonclassical layout made explicit
PPInLineinline decls, with newlines between them
PPNoLayouteverything on a single line
show/hide Instances
defaultMode :: PPHsModeSource
The default mode: pretty-print using the offside rule and sensible defaults.
Produced by Haddock version 2.6.0