haskell-src-exts-1.20.3: 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 #

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

Instances
Pretty SrcSpan # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: SrcSpan -> Doc

prettyPrec :: Int -> SrcSpan -> Doc

Pretty SrcLoc # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: SrcLoc -> Doc

prettyPrec :: Int -> SrcLoc -> Doc

Pretty Tool # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Tool -> Doc

prettyPrec :: Int -> Tool -> Doc

Pretty (Alt l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Alt l -> Doc

prettyPrec :: Int -> Alt l -> Doc

Pretty (FieldUpdate l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: FieldUpdate l -> Doc

prettyPrec :: Int -> FieldUpdate l -> Doc

Pretty (QualStmt l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: QualStmt l -> Doc

prettyPrec :: Int -> QualStmt l -> Doc

Pretty (Stmt l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Stmt l -> Doc

prettyPrec :: Int -> Stmt l -> Doc

Pretty (PatField l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: PatField l -> Doc

prettyPrec :: Int -> PatField l -> Doc

Pretty (RPat l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: RPat l -> Doc

prettyPrec :: Int -> RPat l -> Doc

Pretty (RPatOp l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: RPatOp l -> Doc

prettyPrec :: Int -> RPatOp l -> Doc

Pretty (PXAttr l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: PXAttr l -> Doc

prettyPrec :: Int -> PXAttr l -> Doc

Pretty (Pat l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Pat l -> Doc

prettyPrec :: Int -> Pat l -> Doc

Pretty (RuleVar l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: RuleVar l -> Doc

prettyPrec :: Int -> RuleVar l -> Doc

Pretty (Rule l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Rule l -> Doc

prettyPrec :: Int -> Rule l -> Doc

Pretty (Activation l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Activation l -> Doc

prettyPrec :: Int -> Activation l -> Doc

Pretty (Overlap l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Overlap l -> Doc

prettyPrec :: Int -> Overlap l -> Doc

Pretty (ModulePragma l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ModulePragma l -> Doc

prettyPrec :: Int -> ModulePragma l -> Doc

Pretty (CallConv l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: CallConv l -> Doc

prettyPrec :: Int -> CallConv l -> Doc

Pretty (Safety l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Safety l -> Doc

prettyPrec :: Int -> Safety l -> Doc

Pretty (Splice l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Splice l -> Doc

prettyPrec :: Int -> Splice l -> Doc

Pretty (Bracket l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Bracket l -> Doc

prettyPrec :: Int -> Bracket l -> Doc

Pretty (XAttr l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: XAttr l -> Doc

prettyPrec :: Int -> XAttr l -> Doc

Pretty (XName l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: XName l -> Doc

prettyPrec :: Int -> XName l -> Doc

Pretty (Exp l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Exp l -> Doc

prettyPrec :: Int -> Exp l -> Doc

Pretty (Literal l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Literal l -> Doc

prettyPrec :: Int -> Literal l -> Doc

Pretty (Asst l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Asst l -> Doc

prettyPrec :: Int -> Asst l -> Doc

Pretty (Context l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Context l -> Doc

prettyPrec :: Int -> Context l -> Doc

Pretty (FunDep l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: FunDep l -> Doc

prettyPrec :: Int -> FunDep l -> Doc

Pretty (Kind l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Kind l -> Doc

prettyPrec :: Int -> Kind l -> Doc

Pretty (TyVarBind l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: TyVarBind l -> Doc

prettyPrec :: Int -> TyVarBind l -> Doc

Pretty (Promoted l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Promoted l -> Doc

prettyPrec :: Int -> Promoted l -> Doc

Pretty (MaybePromotedName l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: MaybePromotedName l -> Doc

prettyPrec :: Int -> MaybePromotedName l -> Doc

Pretty (Type l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Type l -> Doc

prettyPrec :: Int -> Type l -> Doc

Pretty (GuardedRhs l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: GuardedRhs l -> Doc

prettyPrec :: Int -> GuardedRhs l -> Doc

Pretty (Rhs l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Rhs l -> Doc

prettyPrec :: Int -> Rhs l -> Doc

Pretty (Unpackedness l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Unpackedness l -> Doc

prettyPrec :: Int -> Unpackedness l -> Doc

Pretty (BangType l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: BangType l -> Doc

prettyPrec :: Int -> BangType l -> Doc

Pretty (InstDecl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: InstDecl l -> Doc

prettyPrec :: Int -> InstDecl l -> Doc

Pretty (ClassDecl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ClassDecl l -> Doc

prettyPrec :: Int -> ClassDecl l -> Doc

Pretty (GadtDecl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: GadtDecl l -> Doc

prettyPrec :: Int -> GadtDecl l -> Doc

Pretty (FieldDecl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: FieldDecl l -> Doc

prettyPrec :: Int -> FieldDecl l -> Doc

Pretty (ConDecl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ConDecl l -> Doc

prettyPrec :: Int -> ConDecl l -> Doc

Pretty (QualConDecl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: QualConDecl l -> Doc

prettyPrec :: Int -> QualConDecl l -> Doc

Pretty (Match l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Match l -> Doc

prettyPrec :: Int -> Match l -> Doc

Pretty (IPBind l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: IPBind l -> Doc

prettyPrec :: Int -> IPBind l -> Doc

Pretty (DerivStrategy l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: DerivStrategy l -> Doc

prettyPrec :: Int -> DerivStrategy l -> Doc

Pretty (Deriving l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Deriving l -> Doc

prettyPrec :: Int -> Deriving l -> Doc

Pretty (InstHead l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: InstHead l -> Doc

prettyPrec :: Int -> InstHead l -> Doc

Pretty (InstRule l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: InstRule l -> Doc

prettyPrec :: Int -> InstRule l -> Doc

Pretty (DeclHead l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: DeclHead l -> Doc

prettyPrec :: Int -> DeclHead l -> Doc

Pretty (ResultSig l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ResultSig l -> Doc

prettyPrec :: Int -> ResultSig l -> Doc

Pretty (InjectivityInfo l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: InjectivityInfo l -> Doc

prettyPrec :: Int -> InjectivityInfo l -> Doc

Pretty (DataOrNew l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: DataOrNew l -> Doc

prettyPrec :: Int -> DataOrNew l -> Doc

Pretty (Role l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Role l -> Doc

prettyPrec :: Int -> Role l -> Doc

Pretty (BooleanFormula l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: BooleanFormula l -> Doc

prettyPrec :: Int -> BooleanFormula l -> Doc

Pretty (Annotation l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Annotation l -> Doc

prettyPrec :: Int -> Annotation l -> Doc

Pretty (TypeEqn l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: TypeEqn l -> Doc

prettyPrec :: Int -> TypeEqn l -> Doc

Pretty (Decl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Decl l -> Doc

prettyPrec :: Int -> Decl l -> Doc

Pretty (Assoc l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Assoc l -> Doc

prettyPrec :: Int -> Assoc l -> Doc

Pretty (ImportSpec l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ImportSpec l -> Doc

prettyPrec :: Int -> ImportSpec l -> Doc

Pretty (ImportSpecList l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ImportSpecList l -> Doc

prettyPrec :: Int -> ImportSpecList l -> Doc

Pretty (ImportDecl l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ImportDecl l -> Doc

prettyPrec :: Int -> ImportDecl l -> Doc

Pretty (Namespace l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Namespace l -> Doc

prettyPrec :: Int -> Namespace l -> Doc

Pretty (ExportSpec l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ExportSpec l -> Doc

prettyPrec :: Int -> ExportSpec l -> Doc

Pretty (ExportSpecList l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ExportSpecList l -> Doc

prettyPrec :: Int -> ExportSpecList l -> Doc

Pretty (ModuleHead l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ModuleHead l -> Doc

prettyPrec :: Int -> ModuleHead l -> Doc

Pretty (Module pos) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Module pos -> Doc

prettyPrec :: Int -> Module pos -> Doc

Pretty (CName l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: CName l -> Doc

prettyPrec :: Int -> CName l -> Doc

Pretty (Op l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Op l -> Doc

prettyPrec :: Int -> Op l -> Doc

Pretty (QOp l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: QOp l -> Doc

prettyPrec :: Int -> QOp l -> Doc

Pretty (IPName l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: IPName l -> Doc

prettyPrec :: Int -> IPName l -> Doc

Pretty (Name l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: Name l -> Doc

prettyPrec :: Int -> Name l -> Doc

Pretty (QName l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: QName l -> Doc

prettyPrec :: Int -> QName l -> Doc

Pretty (SpecialCon l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: SpecialCon l -> Doc

prettyPrec :: Int -> SpecialCon l -> Doc

Pretty (ModuleName l) # 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ModuleName l -> Doc

prettyPrec :: Int -> ModuleName l -> Doc

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

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 #

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)

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 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

type Rep Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Style = D1 (MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" False) (C1 (MetaCons "Style" PrefixI True) (S1 (MetaSel (Just "mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mode) :*: (S1 (MetaSel (Just "lineLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "ribbonsPerLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))))

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 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

type Rep Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Mode = D1 (MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" False) ((C1 (MetaCons "PageMode" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ZigZagMode" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LeftMode" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OneLineMode" PrefixI False) (U1 :: Type -> Type)))

Haskell formatting modes

data PPHsMode #

Pretty-printing parameters.

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

Constructors

PPHsMode 

Fields

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 # 
Instance details

Defined in Language.Haskell.Exts.Pretty

defaultMode :: PPHsMode #

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

Primitive Printers

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

pretty-print with the default style and defaultMode.

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

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