| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Printcess.PrettyPrinting
Contents
- pretty :: Pretty a => State Config () -> a -> String
- prettyPrint :: (MonadIO m, Pretty a) => State Config () -> a -> m ()
- data Config
- cMaxLineWidth :: Lens' Config (Maybe Int)
- cIndentChar :: Lens' Config Char
- cIndentDepth :: Lens' Config Int
- cIndentAfterBreaks :: Lens' Config Int
- cInitIndent :: Lens' Config Int
- cInitPrecedence :: Lens' Config Int
- defConfig :: State Config ()
- class Pretty a where
- data PrettyM a
- (+>) :: (Pretty a, Pretty b) => a -> b -> PrettyM ()
- (~>) :: (Pretty a, Pretty b) => a -> b -> PrettyM ()
- (\>) :: (Pretty a, Pretty b) => a -> b -> PrettyM ()
- indentedByChars :: Pretty a => Int -> a -> PrettyM ()
- indentedBy :: Pretty a => Int -> a -> PrettyM ()
- indented :: Pretty a => a -> PrettyM ()
- block :: Pretty a => [a] -> PrettyM ()
- block' :: Pretty a => [a] -> PrettyM ()
- assocL :: Pretty a => Int -> a -> PrettyM ()
- assocR :: Pretty a => Int -> a -> PrettyM ()
- assocN :: Pretty a => Int -> a -> PrettyM ()
- left :: Pretty a => a -> PrettyM ()
- right :: Pretty a => a -> PrettyM ()
- inner :: Pretty a => a -> PrettyM ()
- data AssocAnn a
- betweenEach :: (Pretty a, Pretty b) => a -> [b] -> PrettyM ()
- beforeEach :: (Pretty a, Pretty b) => a -> [b] -> PrettyM ()
- afterEach :: (Pretty a, Pretty b) => a -> [b] -> PrettyM ()
- ppList :: Pretty a => [a] -> PrettyM ()
- ppListMap :: (Pretty a, Pretty b) => [(a, b)] -> PrettyM ()
- ppMap :: (Pretty a, Pretty b) => Map a b -> PrettyM ()
- bar :: Char -> PrettyM ()
- titleBar :: Pretty a => Char -> a -> PrettyM ()
- nl :: PrettyM ()
- sp :: PrettyM ()
- class Pretty1 f where
- class Pretty2 f where
- type State s = StateT s Identity
- (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
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 xby printing the identifierStringx. - a function application
EApp e1 e2as a left-associative operator of fixity 9 (assocL9), where e1 is the left argument (L) ande2is the right argument (R). The (~>) combinator separates its first argument with a space from its second argument. - a function abstraction
EAbs x eas a right-associative operator of fixity 0 (assocR0), wherexis an inner argument (I) andeis 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
Config
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 .= 0cMaxLineWidth :: 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
booDefault: 4
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
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 |
| Pretty Double Source # | Behaves like |
| Pretty Float Source # | Behaves like |
| Pretty Int Source # | Behaves like |
| Pretty String Source # | In contrast to |
| Pretty a => Pretty (AssocAnn a) Source # | Let the associativity annotations for arguments ( |
| Pretty (PrettyM ()) Source # | This instance makes it possible to nest operators like |
Monad
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 actions using PrettyM ()pp, and combine the actions in
some way resulting in a new action.PrettyM ()
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
Arguments
| :: Pretty a | |
| => Int | Number of characters to increase indentation. |
| -> a | A |
| -> PrettyM () | An action printing the |
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();
-- }"Arguments
| :: Pretty a | |
| => Int | Number of indentation levels to increase.
One indentation level consists of |
| -> a | A |
| -> PrettyM () | An action printing the |
Same as indentedByChars but increases indentation in cIndentDepth steps.
Arguments
| :: Pretty a | |
| => a | A |
| -> PrettyM () | An action printing the |
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.
Constructors
| L a | Print an |
| R a | Print an |
| I a | Print an |
Instances
| Pretty1 AssocAnn Source # | |
| Eq a => Eq (AssocAnn a) Source # | |
| Ord a => Ord (AssocAnn a) Source # | |
| Read a => Read (AssocAnn a) Source # | |
| Show a => Show (AssocAnn a) Source # | |
| Pretty a => Pretty (AssocAnn a) Source # | Let the associativity annotations for arguments ( |
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
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.
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)
(.=) ::MonadStates m =>Iso's a -> a -> m () (.=) ::MonadStates m =>Lens's a -> a -> m () (.=) ::MonadStates m =>Traversal's a -> a -> m () (.=) ::MonadStates m =>Setter's a -> a -> m ()
It puts the state in the monad or it gets the hose again.