haskell-src-exts-1.16.0.1: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer

Copyright(c) Niklas Broberg 2004-2009, (c) The GHC Team, Noel Winstanley 1997-2000
LicenseBSD-style (see the file LICENSE.txt)
MaintainerNiklas Broberg, d00nibro@chalmers.se
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell98

Language.Haskell.Exts.Pretty

Contents

Description

Pretty printer for Haskell with extensions.

Synopsis

Pretty printing

class Pretty a Source

Things that can be pretty-printed, including all the syntactic objects in Language.Haskell.Exts.Syntax and Language.Haskell.Exts.Annotated.Syntax.

Instances

Pretty Tool 
Pretty SrcSpan 
Pretty SrcLoc 
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 Overlap 
Pretty ModulePragma 
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 Promoted 
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 BooleanFormula 
Pretty Annotation 
Pretty TypeEqn 
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 (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) 
SrcInfo l => Pretty (RuleVar l) 
SrcInfo loc => Pretty (Rule loc) 
Pretty (Activation l) 
SrcInfo loc => Pretty (ModulePragma loc) 
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) 
SrcInfo l => Pretty (Asst l) 
SrcInfo l => Pretty (Context l) 
Pretty (FunDep l) 
Pretty (Kind l) 
Pretty (TyVarBind l) 
SrcInfo l => Pretty (Type l) 
SrcInfo loc => Pretty (GuardedRhs loc) 
SrcInfo loc => Pretty (Rhs loc) 
SrcInfo l => Pretty (BangType l) 
SrcInfo loc => Pretty (InstDecl loc) 
SrcInfo loc => Pretty (ClassDecl loc) 
SrcInfo l => Pretty (GadtDecl l) 
SrcInfo l => Pretty (FieldDecl l) 
SrcInfo l => Pretty (ConDecl l) 
SrcInfo l => Pretty (QualConDecl l) 
SrcInfo pos => Pretty (Match pos) 
SrcInfo loc => Pretty (IPBind loc) 
SrcInfo l => Pretty (Deriving l) 
SrcInfo l => Pretty (InstHead l) 
SrcInfo l => Pretty (InstRule l) 
Pretty (DeclHead l) 
Pretty (DataOrNew l) 
SrcInfo loc => Pretty (Annotation loc) 
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) 

prettyPrintStyleMode :: Pretty a => Style -> PPHsMode -> a -> String Source

render the document with a given mode. renderWithMode :: PPHsMode -> Doc -> String renderWithMode = renderStyleMode P.style

render the document with defaultMode. render :: Doc -> String render = renderWithMode defaultMode

pretty-print with a given style and mode.

prettyPrintWithMode :: Pretty a => PPHsMode -> a -> String Source

pretty-print with the default style and a given mode.

prettyPrint :: Pretty a => a -> String Source

pretty-print with the default style and defaultMode.

Pretty-printing styles (from Text.PrettyPrint.HughesPJ)

data Style :: *

A rendering style.

Constructors

Style 

Fields

mode :: Mode

The rendering mode

lineLength :: Int

Length of line, in chars

ribbonsPerLine :: Float

Ratio of ribbon length to line length

style :: Style

The default style (mode=PageMode, lineLength=100, ribbonsPerLine=1.5).

data Mode :: *

Rendering mode.

Constructors

PageMode

Normal

ZigZagMode

With zig-zag cuts

LeftMode

No indentation, infinitely long lines

OneLineMode

All 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 

Fields

classIndent :: Indent

indentation of a class or instance

doIndent :: Indent

indentation of a do-expression

multiIfIndent :: Indent

indentation of the body of a case expression

caseIndent :: Indent

indentation of the body of a multi-if 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?

data PPLayout Source

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

defaultMode :: PPHsMode Source

The default mode: pretty-print using the offside rule and sensible defaults.