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 # 

Methods

pretty :: Tool -> Doc

prettyPrec :: Int -> Tool -> Doc

Pretty SrcSpan Source # 

Methods

pretty :: SrcSpan -> Doc

prettyPrec :: Int -> SrcSpan -> Doc

Pretty SrcLoc Source # 

Methods

pretty :: SrcLoc -> Doc

prettyPrec :: Int -> SrcLoc -> Doc

Pretty Alt Source # 

Methods

pretty :: Alt -> Doc

prettyPrec :: Int -> Alt -> Doc

Pretty FieldUpdate Source # 

Methods

pretty :: FieldUpdate -> Doc

prettyPrec :: Int -> FieldUpdate -> Doc

Pretty QualStmt Source # 

Methods

pretty :: QualStmt -> Doc

prettyPrec :: Int -> QualStmt -> Doc

Pretty Stmt Source # 

Methods

pretty :: Stmt -> Doc

prettyPrec :: Int -> Stmt -> Doc

Pretty PatField Source # 

Methods

pretty :: PatField -> Doc

prettyPrec :: Int -> PatField -> Doc

Pretty RPat Source # 

Methods

pretty :: RPat -> Doc

prettyPrec :: Int -> RPat -> Doc

Pretty RPatOp Source # 

Methods

pretty :: RPatOp -> Doc

prettyPrec :: Int -> RPatOp -> Doc

Pretty PXAttr Source # 

Methods

pretty :: PXAttr -> Doc

prettyPrec :: Int -> PXAttr -> Doc

Pretty Pat Source # 

Methods

pretty :: Pat -> Doc

prettyPrec :: Int -> Pat -> Doc

Pretty RuleVar Source # 

Methods

pretty :: RuleVar -> Doc

prettyPrec :: Int -> RuleVar -> Doc

Pretty Rule Source # 

Methods

pretty :: Rule -> Doc

prettyPrec :: Int -> Rule -> Doc

Pretty Activation Source # 

Methods

pretty :: Activation -> Doc

prettyPrec :: Int -> Activation -> Doc

Pretty Overlap Source # 

Methods

pretty :: Overlap -> Doc

prettyPrec :: Int -> Overlap -> Doc

Pretty ModulePragma Source # 

Methods

pretty :: ModulePragma -> Doc

prettyPrec :: Int -> ModulePragma -> Doc

Pretty CallConv Source # 

Methods

pretty :: CallConv -> Doc

prettyPrec :: Int -> CallConv -> Doc

Pretty Safety Source # 

Methods

pretty :: Safety -> Doc

prettyPrec :: Int -> Safety -> Doc

Pretty Splice Source # 

Methods

pretty :: Splice -> Doc

prettyPrec :: Int -> Splice -> Doc

Pretty Bracket Source # 

Methods

pretty :: Bracket -> Doc

prettyPrec :: Int -> Bracket -> Doc

Pretty XAttr Source # 

Methods

pretty :: XAttr -> Doc

prettyPrec :: Int -> XAttr -> Doc

Pretty XName Source # 

Methods

pretty :: XName -> Doc

prettyPrec :: Int -> XName -> Doc

Pretty Exp Source # 

Methods

pretty :: Exp -> Doc

prettyPrec :: Int -> Exp -> Doc

Pretty Literal Source # 

Methods

pretty :: Literal -> Doc

prettyPrec :: Int -> Literal -> Doc

Pretty Asst Source # 

Methods

pretty :: Asst -> Doc

prettyPrec :: Int -> Asst -> Doc

Pretty FunDep Source # 

Methods

pretty :: FunDep -> Doc

prettyPrec :: Int -> FunDep -> Doc

Pretty Kind Source # 

Methods

pretty :: Kind -> Doc

prettyPrec :: Int -> Kind -> Doc

Pretty TyVarBind Source # 

Methods

pretty :: TyVarBind -> Doc

prettyPrec :: Int -> TyVarBind -> Doc

Pretty Promoted Source # 

Methods

pretty :: Promoted -> Doc

prettyPrec :: Int -> Promoted -> Doc

Pretty Type Source # 

Methods

pretty :: Type -> Doc

prettyPrec :: Int -> Type -> Doc

Pretty GuardedRhs Source # 

Methods

pretty :: GuardedRhs -> Doc

prettyPrec :: Int -> GuardedRhs -> Doc

Pretty Rhs Source # 

Methods

pretty :: Rhs -> Doc

prettyPrec :: Int -> Rhs -> Doc

Pretty BangType Source # 

Methods

pretty :: BangType -> Doc

prettyPrec :: Int -> BangType -> Doc

Pretty InstDecl Source # 

Methods

pretty :: InstDecl -> Doc

prettyPrec :: Int -> InstDecl -> Doc

Pretty ClassDecl Source # 

Methods

pretty :: ClassDecl -> Doc

prettyPrec :: Int -> ClassDecl -> Doc

Pretty GadtDecl Source # 

Methods

pretty :: GadtDecl -> Doc

prettyPrec :: Int -> GadtDecl -> Doc

Pretty ConDecl Source # 

Methods

pretty :: ConDecl -> Doc

prettyPrec :: Int -> ConDecl -> Doc

Pretty QualConDecl Source # 

Methods

pretty :: QualConDecl -> Doc

prettyPrec :: Int -> QualConDecl -> Doc

Pretty Match Source # 

Methods

pretty :: Match -> Doc

prettyPrec :: Int -> Match -> Doc

Pretty IPBind Source # 

Methods

pretty :: IPBind -> Doc

prettyPrec :: Int -> IPBind -> Doc

Pretty DataOrNew Source # 

Methods

pretty :: DataOrNew -> Doc

prettyPrec :: Int -> DataOrNew -> Doc

Pretty Role Source # 

Methods

pretty :: Role -> Doc

prettyPrec :: Int -> Role -> Doc

Pretty BooleanFormula Source # 

Methods

pretty :: BooleanFormula -> Doc

prettyPrec :: Int -> BooleanFormula -> Doc

Pretty Annotation Source # 

Methods

pretty :: Annotation -> Doc

prettyPrec :: Int -> Annotation -> Doc

Pretty TypeEqn Source # 

Methods

pretty :: TypeEqn -> Doc

prettyPrec :: Int -> TypeEqn -> Doc

Pretty Decl Source # 

Methods

pretty :: Decl -> Doc

prettyPrec :: Int -> Decl -> Doc

Pretty Assoc Source # 

Methods

pretty :: Assoc -> Doc

prettyPrec :: Int -> Assoc -> Doc

Pretty ImportSpec Source # 

Methods

pretty :: ImportSpec -> Doc

prettyPrec :: Int -> ImportSpec -> Doc

Pretty ImportDecl Source # 

Methods

pretty :: ImportDecl -> Doc

prettyPrec :: Int -> ImportDecl -> Doc

Pretty Namespace Source # 

Methods

pretty :: Namespace -> Doc

prettyPrec :: Int -> Namespace -> Doc

Pretty ExportSpec Source # 

Methods

pretty :: ExportSpec -> Doc

prettyPrec :: Int -> ExportSpec -> Doc

Pretty Module Source # 

Methods

pretty :: Module -> Doc

prettyPrec :: Int -> Module -> Doc

Pretty CName Source # 

Methods

pretty :: CName -> Doc

prettyPrec :: Int -> CName -> Doc

Pretty Op Source # 

Methods

pretty :: Op -> Doc

prettyPrec :: Int -> Op -> Doc

Pretty QOp Source # 

Methods

pretty :: QOp -> Doc

prettyPrec :: Int -> QOp -> Doc

Pretty IPName Source # 

Methods

pretty :: IPName -> Doc

prettyPrec :: Int -> IPName -> Doc

Pretty Name Source # 

Methods

pretty :: Name -> Doc

prettyPrec :: Int -> Name -> Doc

Pretty QName Source # 

Methods

pretty :: QName -> Doc

prettyPrec :: Int -> QName -> Doc

Pretty SpecialCon Source # 

Methods

pretty :: SpecialCon -> Doc

prettyPrec :: Int -> SpecialCon -> Doc

Pretty ModuleName Source # 

Methods

pretty :: ModuleName -> Doc

prettyPrec :: Int -> ModuleName -> Doc

SrcInfo loc => Pretty (Alt loc) Source # 

Methods

pretty :: Alt loc -> Doc

prettyPrec :: Int -> Alt loc -> Doc

SrcInfo loc => Pretty (FieldUpdate loc) Source # 

Methods

pretty :: FieldUpdate loc -> Doc

prettyPrec :: Int -> FieldUpdate loc -> Doc

SrcInfo loc => Pretty (QualStmt loc) Source # 

Methods

pretty :: QualStmt loc -> Doc

prettyPrec :: Int -> QualStmt loc -> Doc

SrcInfo loc => Pretty (Stmt loc) Source # 

Methods

pretty :: Stmt loc -> Doc

prettyPrec :: Int -> Stmt loc -> Doc

SrcInfo loc => Pretty (PatField loc) Source # 

Methods

pretty :: PatField loc -> Doc

prettyPrec :: Int -> PatField loc -> Doc

SrcInfo loc => Pretty (RPat loc) Source # 

Methods

pretty :: RPat loc -> Doc

prettyPrec :: Int -> RPat loc -> Doc

Pretty (RPatOp l) Source # 

Methods

pretty :: RPatOp l -> Doc

prettyPrec :: Int -> RPatOp l -> Doc

SrcInfo loc => Pretty (PXAttr loc) Source # 

Methods

pretty :: PXAttr loc -> Doc

prettyPrec :: Int -> PXAttr loc -> Doc

SrcInfo loc => Pretty (Pat loc) Source # 

Methods

pretty :: Pat loc -> Doc

prettyPrec :: Int -> Pat loc -> Doc

Pretty (WarningText l) Source # 

Methods

pretty :: WarningText l -> Doc

prettyPrec :: Int -> WarningText l -> Doc

SrcInfo l => Pretty (RuleVar l) Source # 

Methods

pretty :: RuleVar l -> Doc

prettyPrec :: Int -> RuleVar l -> Doc

SrcInfo loc => Pretty (Rule loc) Source # 

Methods

pretty :: Rule loc -> Doc

prettyPrec :: Int -> Rule loc -> Doc

Pretty (Activation l) Source # 

Methods

pretty :: Activation l -> Doc

prettyPrec :: Int -> Activation l -> Doc

SrcInfo loc => Pretty (ModulePragma loc) Source # 

Methods

pretty :: ModulePragma loc -> Doc

prettyPrec :: Int -> ModulePragma loc -> Doc

Pretty (CallConv l) Source # 

Methods

pretty :: CallConv l -> Doc

prettyPrec :: Int -> CallConv l -> Doc

Pretty (Safety l) Source # 

Methods

pretty :: Safety l -> Doc

prettyPrec :: Int -> Safety l -> Doc

SrcInfo loc => Pretty (Splice loc) Source # 

Methods

pretty :: Splice loc -> Doc

prettyPrec :: Int -> Splice loc -> Doc

SrcInfo loc => Pretty (Bracket loc) Source # 

Methods

pretty :: Bracket loc -> Doc

prettyPrec :: Int -> Bracket loc -> Doc

SrcInfo loc => Pretty (XAttr loc) Source # 

Methods

pretty :: XAttr loc -> Doc

prettyPrec :: Int -> XAttr loc -> Doc

Pretty (XName l) Source # 

Methods

pretty :: XName l -> Doc

prettyPrec :: Int -> XName l -> Doc

SrcInfo loc => Pretty (Exp loc) Source # 

Methods

pretty :: Exp loc -> Doc

prettyPrec :: Int -> Exp loc -> Doc

Pretty (Literal l) Source # 

Methods

pretty :: Literal l -> Doc

prettyPrec :: Int -> Literal l -> Doc

SrcInfo l => Pretty (Asst l) Source # 

Methods

pretty :: Asst l -> Doc

prettyPrec :: Int -> Asst l -> Doc

SrcInfo l => Pretty (Context l) Source # 

Methods

pretty :: Context l -> Doc

prettyPrec :: Int -> Context l -> Doc

Pretty (FunDep l) Source # 

Methods

pretty :: FunDep l -> Doc

prettyPrec :: Int -> FunDep l -> Doc

Pretty (Kind l) Source # 

Methods

pretty :: Kind l -> Doc

prettyPrec :: Int -> Kind l -> Doc

Pretty (TyVarBind l) Source # 

Methods

pretty :: TyVarBind l -> Doc

prettyPrec :: Int -> TyVarBind l -> Doc

SrcInfo l => Pretty (Type l) Source # 

Methods

pretty :: Type l -> Doc

prettyPrec :: Int -> Type l -> Doc

SrcInfo loc => Pretty (GuardedRhs loc) Source # 

Methods

pretty :: GuardedRhs loc -> Doc

prettyPrec :: Int -> GuardedRhs loc -> Doc

SrcInfo loc => Pretty (Rhs loc) Source # 

Methods

pretty :: Rhs loc -> Doc

prettyPrec :: Int -> Rhs loc -> Doc

SrcInfo l => Pretty (BangType l) Source # 

Methods

pretty :: BangType l -> Doc

prettyPrec :: Int -> BangType l -> Doc

SrcInfo loc => Pretty (InstDecl loc) Source # 

Methods

pretty :: InstDecl loc -> Doc

prettyPrec :: Int -> InstDecl loc -> Doc

SrcInfo loc => Pretty (ClassDecl loc) Source # 

Methods

pretty :: ClassDecl loc -> Doc

prettyPrec :: Int -> ClassDecl loc -> Doc

SrcInfo l => Pretty (GadtDecl l) Source # 

Methods

pretty :: GadtDecl l -> Doc

prettyPrec :: Int -> GadtDecl l -> Doc

SrcInfo l => Pretty (FieldDecl l) Source # 

Methods

pretty :: FieldDecl l -> Doc

prettyPrec :: Int -> FieldDecl l -> Doc

SrcInfo l => Pretty (ConDecl l) Source # 

Methods

pretty :: ConDecl l -> Doc

prettyPrec :: Int -> ConDecl l -> Doc

SrcInfo l => Pretty (QualConDecl l) Source # 

Methods

pretty :: QualConDecl l -> Doc

prettyPrec :: Int -> QualConDecl l -> Doc

SrcInfo pos => Pretty (Match pos) Source # 

Methods

pretty :: Match pos -> Doc

prettyPrec :: Int -> Match pos -> Doc

SrcInfo loc => Pretty (IPBind loc) Source # 

Methods

pretty :: IPBind loc -> Doc

prettyPrec :: Int -> IPBind loc -> Doc

SrcInfo l => Pretty (Deriving l) Source # 

Methods

pretty :: Deriving l -> Doc

prettyPrec :: Int -> Deriving l -> Doc

SrcInfo l => Pretty (InstHead l) Source # 

Methods

pretty :: InstHead l -> Doc

prettyPrec :: Int -> InstHead l -> Doc

SrcInfo l => Pretty (InstRule l) Source # 

Methods

pretty :: InstRule l -> Doc

prettyPrec :: Int -> InstRule l -> Doc

Pretty (DeclHead l) Source # 

Methods

pretty :: DeclHead l -> Doc

prettyPrec :: Int -> DeclHead l -> Doc

Pretty (DataOrNew l) Source # 

Methods

pretty :: DataOrNew l -> Doc

prettyPrec :: Int -> DataOrNew l -> Doc

SrcInfo loc => Pretty (Annotation loc) Source # 

Methods

pretty :: Annotation loc -> Doc

prettyPrec :: Int -> Annotation loc -> Doc

SrcInfo pos => Pretty (Decl pos) Source # 

Methods

pretty :: Decl pos -> Doc

prettyPrec :: Int -> Decl pos -> Doc

Pretty (Assoc l) Source # 

Methods

pretty :: Assoc l -> Doc

prettyPrec :: Int -> Assoc l -> Doc

Pretty (ImportSpec l) Source # 

Methods

pretty :: ImportSpec l -> Doc

prettyPrec :: Int -> ImportSpec l -> Doc

Pretty (ImportSpecList l) Source # 

Methods

pretty :: ImportSpecList l -> Doc

prettyPrec :: Int -> ImportSpecList l -> Doc

SrcInfo pos => Pretty (ImportDecl pos) Source # 

Methods

pretty :: ImportDecl pos -> Doc

prettyPrec :: Int -> ImportDecl pos -> Doc

Pretty (ExportSpec l) Source # 

Methods

pretty :: ExportSpec l -> Doc

prettyPrec :: Int -> ExportSpec l -> Doc

Pretty (ExportSpecList l) Source # 

Methods

pretty :: ExportSpecList l -> Doc

prettyPrec :: Int -> ExportSpecList l -> Doc

Pretty (ModuleHead l) Source # 

Methods

pretty :: ModuleHead l -> Doc

prettyPrec :: Int -> ModuleHead l -> Doc

SrcInfo pos => Pretty (Module pos) Source # 

Methods

pretty :: Module pos -> Doc

prettyPrec :: Int -> Module pos -> Doc

Pretty (CName l) Source # 

Methods

pretty :: CName l -> Doc

prettyPrec :: Int -> CName l -> Doc

Pretty (Op l) Source # 

Methods

pretty :: Op l -> Doc

prettyPrec :: Int -> Op l -> Doc

Pretty (QOp l) Source # 

Methods

pretty :: QOp l -> Doc

prettyPrec :: Int -> QOp l -> Doc

Pretty (IPName l) Source # 

Methods

pretty :: IPName l -> Doc

prettyPrec :: Int -> IPName l -> Doc

Pretty (Name l) Source # 

Methods

pretty :: Name l -> Doc

prettyPrec :: Int -> Name l -> Doc

Pretty (QName l) Source # 

Methods

pretty :: QName l -> Doc

prettyPrec :: Int -> QName l -> Doc

Pretty (ModuleName l) Source # 

Methods

pretty :: ModuleName l -> Doc

prettyPrec :: Int -> ModuleName l -> Doc

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. Allows us to specify constraints to choose among the many different rendering options.

Constructors

Style 

Fields

  • mode :: Mode

    The rendering mode.

  • lineLength :: Int

    Maximum length of a line, in characters.

  • ribbonsPerLine :: Float

    Ratio of line length to ribbon length. A ribbon refers to the characters on a line excluding indentation. So a lineLength of 100, with a ribbonsPerLine of 2.0 would only allow up to 50 characters of ribbon to be displayed on a line, while allowing it to be indented up to 50 characters.

Instances

Eq Style 

Methods

(==) :: Style -> Style -> Bool #

(/=) :: Style -> Style -> Bool #

Show Style 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style 

Associated Types

type Rep Style :: * -> * #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

type Rep Style 

style :: Style #

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

data Mode :: * #

Rendering mode.

Constructors

PageMode

Normal rendering (lineLength and ribbonsPerLine respected').

ZigZagMode

With zig-zag cuts.

LeftMode

No indentation, infinitely long lines (lineLength ignored), but explicit new lines, i.e., text "one" $$ text "two", are respected.

OneLineMode

All on one line, lineLength ignored and explicit new lines ($$) are turned into spaces.

Instances

Eq Mode 

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

Show Mode 

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode 

Associated Types

type Rep Mode :: * -> * #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

type Rep Mode 
type Rep Mode = D1 (MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.3" False) ((:+:) ((:+:) (C1 (MetaCons "PageMode" PrefixI False) U1) (C1 (MetaCons "ZigZagMode" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LeftMode" PrefixI False) U1) (C1 (MetaCons "OneLineMode" PrefixI False) 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

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.