printcess-0.1.0.3: Pretty printing with indentation, mixfix operators, and automatic line breaks.

Safe HaskellNone
LanguageHaskell2010

Printcess.PrettyPrinting

Contents

Synopsis

Overview

The main features of the printcess pretty printing library are

  • Indentation. Printing-actions are relative to the indentation level of their context. Special actions can be used to control the indentation level. Indentation is automatically inserted after newlines.
  • Automatic parenthesizing of mixfix operators. Special printing-actions can be used to specify the associativity and fixity of operators and to mark the positions of their arguments. This makes it easy to print for example "λx. λy. x y (x y)" instead of "(λx. (λy. ((x y) (x y))))".
  • Automatic line breaks after exceeding a maximum line width. A maximum line width can be specified, after which lines are automatically broken. If the break point is inside a word, it is moved to the left until a white space character is reached. This avoids splitting identifiers into two.

Example

In this section, a small example is presented, which pretty prints a lambda calculus expression.

First we define an abstract syntax tree for lambda calculus expressions.

data Expr
  = EVar String
  | EAbs String Expr
  | EApp Expr Expr

Then we make Expr an instance of the Pretty type class, which declares one method pp. This method takes an Expr and returns a PrettyM () action, which describes how to pretty print the Expr.

instance Pretty Expr where
  pp (EVar x)     = pp x
  pp (EApp e1 e2) = assocL 9 $ L e1 ~> R e2
  pp (EAbs x e)   = assocR 0 $ "λ" +> I x +> "." ~> R e

We print

  • a variable EVar x by printing the identifier String x.
  • a function application EApp e1 e2 as a left-associative operator of fixity 9 (assocL 9), where e1 is the left argument (L) and e2 is the right argument (R). The (~>) combinator separates its first argument with a space from its second argument.
  • a function abstraction EAbs x e as a right-associative operator of fixity 0 (assocR 0), where x is an inner argument (I) and e is the right argument (R). The (+>) combinator behaves as (~>), but without inserting a space.

Then we define a simple test expression e1 representing λx. λy. x y (x y)

e1 :: Expr
e1 = EAbs "x" $ EAbs "y" $ EApp (EApp (EVar "x") (EVar "y"))
                                (EApp (EVar "x") (EVar "y"))

and pretty print it to String using the pretty function

s1, s2 :: String
s1 = pretty defConfig                  e1    -- evaluates to "λx. λy. x y (x y)"
s2 = pretty (cMaxLineWidth .= Just 12) e1    -- evaluates to "λx. λy. x y
                                             --                   (x y)"

Rendering

pretty Source #

Arguments

:: Pretty a 
=> State Config ()

Updates for the default pretty printing Config.

-> a

A Pretty printable a.

-> String

The pretty printed a.

Render a Pretty printable a to String using a Config, that specifies how the a should be rendered. For example

pretty defConfig (1 :: Int)  -- evaluates to "1"

prettyPrint Source #

Arguments

:: (MonadIO m, Pretty a) 
=> State Config ()

Updates for the default pretty printing Config.

-> a

A Pretty printable a.

-> m ()

An IO action pretty printing the a to stdout.

Render a Pretty printable a to stdout using a Config, that specifies how the a should be rendered.

Convenience function, defined as:

prettyPrint c = liftIO . putStrLn . pretty c

Config

data Config Source #

A Config allows to specify various pretty printing options, e.g. the maximum line width.

As the rendering functions, like pretty, take updates to an internal default Config, only the lenses of the Config fields are exported.

A custom Config can be specified as in the following example:

foo :: String
foo = pretty config "foo bar baz"
  where config :: State Config ()
        config = do cMaxLineWidth      .= Just 6
                    cInitIndent        .= 2
                    cIndentAfterBreaks .= 0

cMaxLineWidth :: Lens' Config (Maybe Int) Source #

When a line gets longer, it is broken after the latest space, that still allows the line to remain below this maximum.

If there is no such space, an over-long line with a single indented word is printed.

This guarantees both progress and not to break identifiers into parts.

Default: Just 80

cIndentChar :: Lens' Config Char Source #

The character used for indentation. Usually ' ' for spaces or '\t' for tabs.

Default: ' '

cIndentDepth :: Lens' Config Int Source #

How many cIndentChar characters for one indentation level.

Default: 2

cIndentAfterBreaks :: Lens' Config Int Source #

How many cIndentChar characters to indent additionally, when a line break occurs, because cMaxLineWidth was exceeded.

Assuming the line to print has to be broken multiple times, the indentation of all resulting lines, except the first one, is increased by this amount. For example

pretty (do cMaxLineWidth .= Just 8; cIndentAfterBreaks .= 4) "foo bar baz boo"

evaluates to

foo bar
    baz
    boo

Default: 4

cInitIndent :: Lens' Config Int Source #

Indentation level to start pretty printing with.

Default: 0

cInitPrecedence :: Lens' Config Int Source #

Precendence level to start pretty printing with.

Default: (-1)

defConfig :: State Config () Source #

Leaves the default Config unchanged and returns ().

Convenience function defined as:

defConfig = pure ()

See example in pretty.

Type Class

class Pretty a where Source #

Instanciating this class for a type, declares how values of that type should be pretty printed.

As pretty printing may depend on some context, e.g. the current indentation level, a State monad for pretty printing (PrettyM) is used.

A default implementation is provided copying behavior from a Show instance. This can be convenient for deriving Pretty, e.g. for base types or debugging. The default implementation is defined by pp = pp . show.

Methods

pp :: a -> PrettyM () Source #

Pretty print an a as a PrettyM action.

pp :: Show a => a -> PrettyM () Source #

Pretty print an a as a PrettyM action.

Instances

Pretty Char Source #

In contrast to Show, 'c' is printed as "c" and not "'c'".

Methods

pp :: Char -> PrettyM () Source #

Pretty Double Source #

Behaves like Show: 1.2 is printed to "1.2".

Methods

pp :: Double -> PrettyM () Source #

Pretty Float Source #

Behaves like Show: 1.2 is printed to "1.2".

Methods

pp :: Float -> PrettyM () Source #

Pretty Int Source #

Behaves like Show: 1 is printed to "1".

Methods

pp :: Int -> PrettyM () Source #

Pretty String Source #

In contrast to Show, "foo" is printed as "foo" and not "\"foo\"". Most of the other instances are defined in terms of this instance. If the String contains newline characters ('\n'), indentation is inserted automatically afterwards. If the current line gets too long, it is automatically broken.

Methods

pp :: String -> PrettyM () Source #

Pretty a => Pretty (AssocAnn a) Source #

Let the associativity annotations for arguments (L, R, I) behave as the left, right, and inner functions.

Methods

pp :: AssocAnn a -> PrettyM () Source #

Pretty (PrettyM ()) Source #

This instance makes it possible to nest operators like (+>). Implemented as: pp = id

Methods

pp :: PrettyM () -> PrettyM () Source #

Monad

data PrettyM a Source #

The PrettyM monad is run in the pretty printing process, e.g. in pretty or prettyPrint.

PrettyM is internally a State monad manipulating a Config and a list of pretty printed lines.

Most of the combinators from this library take values of Pretty printable types, convert them to PrettyM () actions using pp, and combine the actions in some way resulting in a new PrettyM () action.

Instances

Monad PrettyM Source # 

Methods

(>>=) :: PrettyM a -> (a -> PrettyM b) -> PrettyM b #

(>>) :: PrettyM a -> PrettyM b -> PrettyM b #

return :: a -> PrettyM a #

fail :: String -> PrettyM a #

Functor PrettyM Source # 

Methods

fmap :: (a -> b) -> PrettyM a -> PrettyM b #

(<$) :: a -> PrettyM b -> PrettyM a #

Applicative PrettyM Source # 

Methods

pure :: a -> PrettyM a #

(<*>) :: PrettyM (a -> b) -> PrettyM a -> PrettyM b #

(*>) :: PrettyM a -> PrettyM b -> PrettyM b #

(<*) :: PrettyM a -> PrettyM b -> PrettyM a #

Pretty (PrettyM ()) Source #

This instance makes it possible to nest operators like (+>). Implemented as: pp = id

Methods

pp :: PrettyM () -> PrettyM () Source #

Sequencing

(+>) :: (Pretty a, Pretty b) => a -> b -> PrettyM () infixr 5 Source #

Print two Pretty printable things in sequence.

Example:

pretty defConfig $ "x" +> 1  -- ↪ "x1"

Convenience function, defined as

a +> b = pp a >> pp b

(~>) :: (Pretty a, Pretty b) => a -> b -> PrettyM () infixr 4 Source #

Print two Pretty printable things in sequence, separated by a space.

Example:

pretty defConfig $ "x" ~> 1  -- ↪ "x 1"

Convenience function, defined as

a ~> b = a +> " " +> b

(\>) :: (Pretty a, Pretty b) => a -> b -> PrettyM () infixr 3 Source #

Print two Pretty printable things in sequence, separated by a newline.

Example:

pretty defConfig $ "x" \> 1  -- ↪ "x
                                   1"

Convenience function, defined as

a \> b = a +> "\n" +> b

Indentation

indentedByChars Source #

Arguments

:: Pretty a 
=> Int

Number of characters to increase indentation.

-> a

A Pretty printable a

-> PrettyM ()

An action printing the a with increased indentation.

Print an a with indentation increased by a certain amount of cIndentChar characters.

Example:

pretty defConfig $
  "while (true) {" \>
  indentedByChars 2 ("f();" \> "g();") \>
  "}"
-- ↪ "while (true) {
--      f();
--      g();
--    }"

indentedBy Source #

Arguments

:: Pretty a 
=> Int

Number of indentation levels to increase. One indentation level consists of cIndentDepth characters.

-> a

A Pretty printable a

-> PrettyM ()

An action printing the a with increased indentation.

Same as indentedByChars but increases indentation in cIndentDepth steps.

indented Source #

Arguments

:: Pretty a 
=> a

A Pretty printable a

-> PrettyM ()

An action printing the a indented 1 level deeper.

Convenience function defined as:

indented = indentedBy 1

block :: Pretty a => [a] -> PrettyM () Source #

Print a [a] as a block, meaning that the indentation level is increased, and each a is printed on a single line.

Example:

pretty defConfig $ "do" ~> block ["putStrLn hello", "putStrLn world"]
-- ↪ "do
--      putStrLn hello
--      putStrLn world"

block' :: Pretty a => [a] -> PrettyM () Source #

Same as block, but starts the block on the current line.

Example:

pretty defConfig $ "do" ~> block' ["putStrLn hello", "putStrLn world"]
-- ↪ "do putStrLn hello
--       putStrLn world"

Associativity & Fixity

assocL :: Pretty a => Int -> a -> PrettyM () Source #

Print an a as a left-associative operator of a certain fixity.

assocR :: Pretty a => Int -> a -> PrettyM () Source #

Print an a as a right-associative operator of a certain fixity.

assocN :: Pretty a => Int -> a -> PrettyM () Source #

Print an a as a non-associative operator of a certain fixity.

left :: Pretty a => a -> PrettyM () Source #

Print an a as the left argument of a mixfix operator.

right :: Pretty a => a -> PrettyM () Source #

Print an a as the right argument of a mixfix operator.

inner :: Pretty a => a -> PrettyM () Source #

Print an a as an inner argument of a mixfix operator.

data AssocAnn a Source #

The constructors of this type can be used as short forms of left, right, and inner.

Constructors

L a

Print an a as the left argument of a mixfix operator (behaves like left).

R a

Print an a as the right argument of a mixfix operator (behaves like right).

I a

Print an a as the inner argument of a mixfix operator (behaves like inner).

Instances

Pretty1 AssocAnn Source # 

Methods

pp1 :: Pretty a => AssocAnn a -> PrettyM () Source #

Eq a => Eq (AssocAnn a) Source # 

Methods

(==) :: AssocAnn a -> AssocAnn a -> Bool #

(/=) :: AssocAnn a -> AssocAnn a -> Bool #

Ord a => Ord (AssocAnn a) Source # 

Methods

compare :: AssocAnn a -> AssocAnn a -> Ordering #

(<) :: AssocAnn a -> AssocAnn a -> Bool #

(<=) :: AssocAnn a -> AssocAnn a -> Bool #

(>) :: AssocAnn a -> AssocAnn a -> Bool #

(>=) :: AssocAnn a -> AssocAnn a -> Bool #

max :: AssocAnn a -> AssocAnn a -> AssocAnn a #

min :: AssocAnn a -> AssocAnn a -> AssocAnn a #

Read a => Read (AssocAnn a) Source # 
Show a => Show (AssocAnn a) Source # 

Methods

showsPrec :: Int -> AssocAnn a -> ShowS #

show :: AssocAnn a -> String #

showList :: [AssocAnn a] -> ShowS #

Pretty a => Pretty (AssocAnn a) Source #

Let the associativity annotations for arguments (L, R, I) behave as the left, right, and inner functions.

Methods

pp :: AssocAnn a -> PrettyM () Source #

Folding Pretty Things

betweenEach :: (Pretty a, Pretty b) => a -> [b] -> PrettyM () infixl 6 Source #

Print an a between each b.

Examples:

pretty defConfig $ "," `betweenEach` []          -- ↪ ""
pretty defConfig $ "," `betweenEach` ["x"]       -- ↪ "x"
pretty defConfig $ "," `betweenEach` ["x", "y"]  -- ↪ "x,y"

beforeEach :: (Pretty a, Pretty b) => a -> [b] -> PrettyM () infixl 6 Source #

Print an a before each b.

Examples:

pretty defConfig $ "," `beforeEach` []          -- ↪ ""
pretty defConfig $ "," `beforeEach` ["x"]       -- ↪ ",x"
pretty defConfig $ "," `beforeEach` ["x", "y"]  -- ↪ ",x,y"

afterEach :: (Pretty a, Pretty b) => a -> [b] -> PrettyM () infixl 6 Source #

Print an a after each b.

Examples:

pretty defConfig $ "," `afterEach` []          -- ↪ ""
pretty defConfig $ "," `afterEach` ["x"]       -- ↪ "x,"
pretty defConfig $ "," `afterEach` ["x", "y"]  -- ↪ "x,y,"

ppList :: Pretty a => [a] -> PrettyM () Source #

Print a [a] similar to its Show instance.

Example:

pretty defConfig $ ppList [ "x", "y" ]  -- ↪ "[ x, y ]"

ppListMap :: (Pretty a, Pretty b) => [(a, b)] -> PrettyM () Source #

Print a list map [(k,v)] as ppList, but render (k,v) pairs as "k → v".

Example:

pretty defConfig $ ppListMap [ ("k1", "v1"), ("k2", "v2") ]
-- ↪ "[ k1 → v1, k2 → v2 ]"

ppMap :: (Pretty a, Pretty b) => Map a b -> PrettyM () Source #

Print a Data.Map in the same way as ppListMap.

Other combinators

bar :: Char -> PrettyM () Source #

Print a horizontal bar consisting of a Char as long as cMaxLineWidth (or 80 if it is Nothing).

Example:

pretty defConfig $ bar '-'
-- ↪ "-----------------------------------------…"

titleBar :: Pretty a => Char -> a -> PrettyM () Source #

Print a horizontal bar consisting of a Char as long as cMaxLineWidth (or 80 if it is Nothing). The horizontal bar has a title String printed at column 6.

Example:

pretty defConfig $ titleBar '-' "Foo"
-- ↪ "----- Foo -------------------------------…"

Constants

nl :: PrettyM () Source #

Print a newline (line break).

sp :: PrettyM () Source #

Print a space.

Lifted Type Classes

class Pretty1 f where Source #

The Pretty1 type class lifts Pretty printing to unary type constructors. It can be used in special cases to abstract over type constructors which are Pretty printable for any Pretty printable type argument.

Methods

pp1 :: Pretty a => f a -> PrettyM () Source #

pp1 :: Pretty (f a) => f a -> PrettyM () Source #

Instances

class Pretty2 f where Source #

The Pretty2 type class lifts Pretty printing to binary type constructors. It can be used in special cases to abstract over type constructors which are Pretty printable for any Pretty printable type arguments.

Methods

pp2 :: (Pretty a, Pretty b) => f a b -> PrettyM () Source #

pp2 :: Pretty (f a b) => f a b -> PrettyM () Source #

Reexports

type State s = StateT s Identity #

A state monad parameterized by the type s of the state to carry.

The return function leaves the state unchanged, while >>= uses the final state of the first computation as the initial state of the second.

(.=) :: MonadState s m => ASetter s s a b -> b -> m () infix 4 #

Replace the target of a Lens or all of the targets of a Setter or Traversal in our monadic state with a new value, irrespective of the old.

This is an infix version of assign.

>>> execState (do _1 .= c; _2 .= d) (a,b)
(c,d)
>>> execState (both .= c) (a,b)
(c,c)
(.=) :: MonadState s m => Iso' s a       -> a -> m ()
(.=) :: MonadState s m => Lens' s a      -> a -> m ()
(.=) :: MonadState s m => Traversal' s a -> a -> m ()
(.=) :: MonadState s m => Setter' s a    -> a -> m ()

It puts the state in the monad or it gets the hose again.