haskell-src-1.0.4.1: Support for manipulating Haskell source code
Copyright(c) The GHC Team Noel Winstanley 1997-2000
LicenseBSD-3-Clause
MaintainerAndreas Abel
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Pretty

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

Instances details
Pretty HsAlt Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsAlt -> Doc

prettyPrec :: Int -> HsAlt -> Doc

Pretty HsAssoc Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsAssoc -> Doc

prettyPrec :: Int -> HsAssoc -> Doc

Pretty HsBangType Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsBangType -> Doc

prettyPrec :: Int -> HsBangType -> Doc

Pretty HsCName Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsCName -> Doc

prettyPrec :: Int -> HsCName -> Doc

Pretty HsConDecl Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsConDecl -> Doc

prettyPrec :: Int -> HsConDecl -> Doc

Pretty HsDecl Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsDecl -> Doc

prettyPrec :: Int -> HsDecl -> Doc

Pretty HsExp Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsExp -> Doc

prettyPrec :: Int -> HsExp -> Doc

Pretty HsExportSpec Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsExportSpec -> Doc

prettyPrec :: Int -> HsExportSpec -> Doc

Pretty HsFieldUpdate Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsFieldUpdate -> Doc

prettyPrec :: Int -> HsFieldUpdate -> Doc

Pretty HsGuardedAlt Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsGuardedAlt -> Doc

prettyPrec :: Int -> HsGuardedAlt -> Doc

Pretty HsGuardedAlts Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsGuardedAlts -> Doc

prettyPrec :: Int -> HsGuardedAlts -> Doc

Pretty HsGuardedRhs Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsGuardedRhs -> Doc

prettyPrec :: Int -> HsGuardedRhs -> Doc

Pretty HsImportDecl Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsImportDecl -> Doc

prettyPrec :: Int -> HsImportDecl -> Doc

Pretty HsImportSpec Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsImportSpec -> Doc

prettyPrec :: Int -> HsImportSpec -> Doc

Pretty HsLiteral Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsLiteral -> Doc

prettyPrec :: Int -> HsLiteral -> Doc

Pretty HsMatch Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsMatch -> Doc

prettyPrec :: Int -> HsMatch -> Doc

Pretty HsModule Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsModule -> Doc

prettyPrec :: Int -> HsModule -> Doc

Pretty HsName Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsName -> Doc

prettyPrec :: Int -> HsName -> Doc

Pretty HsOp Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsOp -> Doc

prettyPrec :: Int -> HsOp -> Doc

Pretty HsPat Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsPat -> Doc

prettyPrec :: Int -> HsPat -> Doc

Pretty HsPatField Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsPatField -> Doc

prettyPrec :: Int -> HsPatField -> Doc

Pretty HsQName Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsQName -> Doc

prettyPrec :: Int -> HsQName -> Doc

Pretty HsQOp Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsQOp -> Doc

prettyPrec :: Int -> HsQOp -> Doc

Pretty HsQualType Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsQualType -> Doc

prettyPrec :: Int -> HsQualType -> Doc

Pretty HsRhs Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsRhs -> Doc

prettyPrec :: Int -> HsRhs -> Doc

Pretty HsSafety Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsSafety -> Doc

prettyPrec :: Int -> HsSafety -> Doc

Pretty HsStmt Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsStmt -> Doc

prettyPrec :: Int -> HsStmt -> Doc

Pretty HsType Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

pretty :: HsType -> Doc

prettyPrec :: Int -> HsType -> Doc

Pretty Module Source # 
Instance details

Defined in Language.Haskell.Pretty

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 #

Constructors

Style 

Fields

Instances

Instances details
Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

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-b893" '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))))

Methods

from :: Style -> Rep Style x

to :: Rep Style x -> Style

Show Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Style -> ShowS

show :: Style -> String

showList :: [Style] -> ShowS

Eq Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

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-b893" '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))))

data Mode #

Instances

Instances details
Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

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-b893" '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)))

Methods

from :: Mode -> Rep Mode x

to :: Rep Mode x -> Mode

Show Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Mode -> ShowS

show :: Mode -> String

showList :: [Mode] -> ShowS

Eq Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

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-b893" '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 Source #

Pretty-printing parameters.

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

Constructors

PPHsMode 

Fields

type Indent = Int Source #

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

Instances details
Eq PPLayout Source # 
Instance details

Defined in Language.Haskell.Pretty

Methods

(==) :: PPLayout -> PPLayout -> Bool

(/=) :: PPLayout -> PPLayout -> Bool

defaultMode :: PPHsMode Source #

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