haskell-src-1.0.3.0: Support for manipulating Haskell source code

Copyright(c) The GHC Team Noel Winstanley 1997-2000
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Pretty

Contents

Description

Pretty printer for Haskell.

Synopsis

Pretty printing

class Pretty a Source #

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

Instances

Pretty HsGuardedAlt Source # 

Methods

pretty :: HsGuardedAlt -> Doc

prettyPrec :: Int -> HsGuardedAlt -> Doc

Pretty HsGuardedAlts Source # 

Methods

pretty :: HsGuardedAlts -> Doc

prettyPrec :: Int -> HsGuardedAlts -> Doc

Pretty HsAlt Source # 

Methods

pretty :: HsAlt -> Doc

prettyPrec :: Int -> HsAlt -> Doc

Pretty HsFieldUpdate Source # 

Methods

pretty :: HsFieldUpdate -> Doc

prettyPrec :: Int -> HsFieldUpdate -> Doc

Pretty HsStmt Source # 

Methods

pretty :: HsStmt -> Doc

prettyPrec :: Int -> HsStmt -> Doc

Pretty HsPatField Source # 

Methods

pretty :: HsPatField -> Doc

prettyPrec :: Int -> HsPatField -> Doc

Pretty HsPat Source # 

Methods

pretty :: HsPat -> Doc

prettyPrec :: Int -> HsPat -> Doc

Pretty HsExp Source # 

Methods

pretty :: HsExp -> Doc

prettyPrec :: Int -> HsExp -> Doc

Pretty HsLiteral Source # 

Methods

pretty :: HsLiteral -> Doc

prettyPrec :: Int -> HsLiteral -> Doc

Pretty HsType Source # 

Methods

pretty :: HsType -> Doc

prettyPrec :: Int -> HsType -> Doc

Pretty HsQualType Source # 

Methods

pretty :: HsQualType -> Doc

prettyPrec :: Int -> HsQualType -> Doc

Pretty HsSafety Source # 

Methods

pretty :: HsSafety -> Doc

prettyPrec :: Int -> HsSafety -> Doc

Pretty HsGuardedRhs Source # 

Methods

pretty :: HsGuardedRhs -> Doc

prettyPrec :: Int -> HsGuardedRhs -> Doc

Pretty HsRhs Source # 

Methods

pretty :: HsRhs -> Doc

prettyPrec :: Int -> HsRhs -> Doc

Pretty HsBangType Source # 

Methods

pretty :: HsBangType -> Doc

prettyPrec :: Int -> HsBangType -> Doc

Pretty HsConDecl Source # 

Methods

pretty :: HsConDecl -> Doc

prettyPrec :: Int -> HsConDecl -> Doc

Pretty HsMatch Source # 

Methods

pretty :: HsMatch -> Doc

prettyPrec :: Int -> HsMatch -> Doc

Pretty HsDecl Source # 

Methods

pretty :: HsDecl -> Doc

prettyPrec :: Int -> HsDecl -> Doc

Pretty HsAssoc Source # 

Methods

pretty :: HsAssoc -> Doc

prettyPrec :: Int -> HsAssoc -> Doc

Pretty HsImportSpec Source # 

Methods

pretty :: HsImportSpec -> Doc

prettyPrec :: Int -> HsImportSpec -> Doc

Pretty HsImportDecl Source # 

Methods

pretty :: HsImportDecl -> Doc

prettyPrec :: Int -> HsImportDecl -> Doc

Pretty HsExportSpec Source # 

Methods

pretty :: HsExportSpec -> Doc

prettyPrec :: Int -> HsExportSpec -> Doc

Pretty HsModule Source # 

Methods

pretty :: HsModule -> Doc

prettyPrec :: Int -> HsModule -> Doc

Pretty HsCName Source # 

Methods

pretty :: HsCName -> Doc

prettyPrec :: Int -> HsCName -> Doc

Pretty HsOp Source # 

Methods

pretty :: HsOp -> Doc

prettyPrec :: Int -> HsOp -> Doc

Pretty HsQOp Source # 

Methods

pretty :: HsQOp -> Doc

prettyPrec :: Int -> HsQOp -> Doc

Pretty HsName Source # 

Methods

pretty :: HsName -> Doc

prettyPrec :: Int -> HsName -> Doc

Pretty HsQName Source # 

Methods

pretty :: HsQName -> Doc

prettyPrec :: Int -> HsQName -> Doc

Pretty Module Source # 

Methods

pretty :: Module -> Doc

prettyPrec :: Int -> Module -> Doc

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

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 
type Rep Style = D1 * (MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.3" False) (C1 * (MetaCons "Style" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "mode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Mode)) ((:*:) * (S1 * (MetaSel (Just Symbol "lineLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "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 

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.