haskell-src-exts-1.17.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
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 Source 
Pretty SrcSpan Source 
Pretty SrcLoc Source 
Pretty Alt Source 
Pretty FieldUpdate Source 
Pretty QualStmt Source 
Pretty Stmt Source 
Pretty PatField Source 
Pretty RPat Source 
Pretty RPatOp Source 
Pretty PXAttr Source 
Pretty Pat Source 
Pretty RuleVar Source 
Pretty Rule Source 
Pretty Activation Source 
Pretty Overlap Source 
Pretty ModulePragma Source 
Pretty CallConv Source 
Pretty Safety Source 
Pretty Splice Source 
Pretty Bracket Source 
Pretty XAttr Source 
Pretty XName Source 
Pretty Exp Source 
Pretty Literal Source 
Pretty Asst Source 
Pretty FunDep Source 
Pretty Kind Source 
Pretty TyVarBind Source 
Pretty Promoted Source 
Pretty Type Source 
Pretty GuardedRhs Source 
Pretty Rhs Source 
Pretty BangType Source 
Pretty InstDecl Source 
Pretty ClassDecl Source 
Pretty GadtDecl Source 
Pretty ConDecl Source 
Pretty QualConDecl Source 
Pretty Match Source 
Pretty IPBind Source 
Pretty DataOrNew Source 
Pretty Role Source 
Pretty BooleanFormula Source 
Pretty Annotation Source 
Pretty TypeEqn Source 
Pretty Decl Source 
Pretty Assoc Source 
Pretty ImportSpec Source 
Pretty ImportDecl Source 
Pretty Namespace Source 
Pretty ExportSpec Source 
Pretty Module Source 
Pretty CName Source 
Pretty Op Source 
Pretty QOp Source 
Pretty IPName Source 
Pretty Name Source 
Pretty QName Source 
Pretty SpecialCon Source 
Pretty ModuleName Source 
SrcInfo loc => Pretty (Alt loc) Source 
SrcInfo loc => Pretty (FieldUpdate loc) Source 
SrcInfo loc => Pretty (QualStmt loc) Source 
SrcInfo loc => Pretty (Stmt loc) Source 
SrcInfo loc => Pretty (PatField loc) Source 
SrcInfo loc => Pretty (RPat loc) Source 
Pretty (RPatOp l) Source 
SrcInfo loc => Pretty (PXAttr loc) Source 
SrcInfo loc => Pretty (Pat loc) Source 
Pretty (WarningText l) Source 
SrcInfo l => Pretty (RuleVar l) Source 
SrcInfo loc => Pretty (Rule loc) Source 
Pretty (Activation l) Source 
SrcInfo loc => Pretty (ModulePragma loc) Source 
Pretty (CallConv l) Source 
Pretty (Safety l) Source 
SrcInfo loc => Pretty (Splice loc) Source 
SrcInfo loc => Pretty (Bracket loc) Source 
SrcInfo loc => Pretty (XAttr loc) Source 
Pretty (XName l) Source 
SrcInfo loc => Pretty (Exp loc) Source 
Pretty (Literal l) Source 
SrcInfo l => Pretty (Asst l) Source 
SrcInfo l => Pretty (Context l) Source 
Pretty (FunDep l) Source 
Pretty (Kind l) Source 
Pretty (TyVarBind l) Source 
SrcInfo l => Pretty (Type l) Source 
SrcInfo loc => Pretty (GuardedRhs loc) Source 
SrcInfo loc => Pretty (Rhs loc) Source 
SrcInfo l => Pretty (BangType l) Source 
SrcInfo loc => Pretty (InstDecl loc) Source 
SrcInfo loc => Pretty (ClassDecl loc) Source 
SrcInfo l => Pretty (GadtDecl l) Source 
SrcInfo l => Pretty (FieldDecl l) Source 
SrcInfo l => Pretty (ConDecl l) Source 
SrcInfo l => Pretty (QualConDecl l) Source 
SrcInfo pos => Pretty (Match pos) Source 
SrcInfo loc => Pretty (IPBind loc) Source 
SrcInfo l => Pretty (Deriving l) Source 
SrcInfo l => Pretty (InstHead l) Source 
SrcInfo l => Pretty (InstRule l) Source 
Pretty (DeclHead l) Source 
Pretty (DataOrNew l) Source 
SrcInfo loc => Pretty (Annotation loc) Source 
SrcInfo pos => Pretty (Decl pos) Source 
Pretty (Assoc l) Source 
Pretty (ImportSpec l) Source 
Pretty (ImportSpecList l) Source 
SrcInfo pos => Pretty (ImportDecl pos) Source 
Pretty (ExportSpec l) Source 
Pretty (ExportSpecList l) Source 
Pretty (ModuleHead l) Source 
SrcInfo pos => Pretty (Module pos) Source 
Pretty (CName l) Source 
Pretty (Op l) Source 
Pretty (QOp l) Source 
Pretty (IPName l) Source 
Pretty (Name l) Source 
Pretty (QName l) Source 
Pretty (ModuleName l) Source 

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 line length to ribbon length

Instances

Eq Style 
Show Style 
Generic Style 
type Rep Style = D1 D1Style (C1 C1_0Style ((:*:) (S1 S1_0_0Style (Rec0 Mode)) ((:*:) (S1 S1_0_1Style (Rec0 Int)) (S1 S1_0_2Style (Rec0 Float))))) 

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

Instances

Eq Mode 
Show Mode 
Generic Mode 
type Rep Mode = D1 D1Mode ((:+:) ((:+:) (C1 C1_0Mode U1) (C1 C1_1Mode U1)) ((:+:) (C1 C1_2Mode U1) (C1 C1_3Mode U1))) 

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.

Primitive Printers

prettyPrim :: Pretty a => a -> Doc Source

pretty-print with the default style and defaultMode.

prettyPrimWithMode :: Pretty a => PPHsMode -> a -> Doc Source

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