CoreErlang-0.0.4: Manipulating Core Erlang source code

Copyright(c) Henrique Ferreiro García 2008
(c) David Castro Pérez 2008
LicenseBSD-style (see the file LICENSE)
MaintainerAlex Kropivny <alex.kropivny@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Language.CoreErlang.Pretty

Contents

Description

Pretty printer for CoreErlang.

Synopsis

Pretty printing

class Pretty a Source #

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

Instances

Pretty TimeOut Source # 

Methods

pretty :: TimeOut -> Doc

prettyPrec :: Int -> TimeOut -> Doc

Pretty Guard Source # 

Methods

pretty :: Guard -> Doc

prettyPrec :: Int -> Guard -> Doc

Pretty Alias Source # 

Methods

pretty :: Alias -> Doc

prettyPrec :: Int -> Alias -> Doc

Pretty Pat Source # 

Methods

pretty :: Pat -> Doc

prettyPrec :: Int -> Pat -> Doc

Pretty Pats Source # 

Methods

pretty :: Pats -> Doc

prettyPrec :: Int -> Pats -> Doc

Pretty Alt Source # 

Methods

pretty :: Alt -> Doc

prettyPrec :: Int -> Alt -> Doc

Pretty Exp Source # 

Methods

pretty :: Exp -> Doc

prettyPrec :: Int -> Exp -> Doc

Pretty Exps Source # 

Methods

pretty :: Exps -> Doc

prettyPrec :: Int -> Exps -> Doc

Pretty Literal Source # 

Methods

pretty :: Literal -> Doc

prettyPrec :: Int -> Literal -> Doc

Pretty FunDef Source # 

Methods

pretty :: FunDef -> Doc

prettyPrec :: Int -> FunDef -> Doc

Pretty Const Source # 

Methods

pretty :: Const -> Doc

prettyPrec :: Int -> Const -> Doc

Pretty Module Source # 

Methods

pretty :: Module -> Doc

prettyPrec :: Int -> Module -> Doc

Pretty Function Source # 

Methods

pretty :: Function -> Doc

prettyPrec :: Int -> Function -> Doc

Pretty Atom Source # 

Methods

pretty :: Atom -> Doc

prettyPrec :: Int -> Atom -> Doc

Pretty a => Pretty (Ann a) Source # 

Methods

pretty :: Ann a -> Doc

prettyPrec :: Int -> Ann a -> Doc

Pretty a => Pretty (List a) Source # 

Methods

pretty :: List a -> Doc

prettyPrec :: Int -> List a -> Doc

Pretty a => Pretty (BitString a) Source # 

Methods

pretty :: BitString a -> Doc

prettyPrec :: Int -> BitString a -> Doc

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

pretty-print with a given style and mode.

prettyPrintWithMode :: Pretty a => PPMode -> 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 *))))

CoreErlang formatting modes

data PPMode Source #

Pretty-printing parameters.

Constructors

PPMode 

Fields

data PPLayout Source #

Varieties of layout we can use.

Constructors

PPDefault

classical layout

PPNoLayout

everything on a single line

Instances

defaultMode :: PPMode Source #

The default mode: pretty-print using sensible defaults.