Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Andy Gill <andygill@ku.edu> |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
Provides a collection of pretty printer combinators, a set of API's that provides a way to easily print out text in a consistent format of your choosing.
Originally designed by John Hughes's and Simon Peyton Jones's.
Marking added by Andy Gill, Oct 08.
For more information you can refer to the original paper that serves as the basis for this libraries design: The Design -- of a Pretty-printing Library by John Hughes, in Advanced Functional Programming, 1995
- type Doc = MDoc ()
- data MDoc a
- data TextDetails a
- char :: Char -> MDoc a
- text :: String -> MDoc a
- ptext :: String -> MDoc a
- sizedText :: Int -> String -> MDoc a
- zeroWidthText :: String -> MDoc a
- int :: Int -> MDoc a
- integer :: Integer -> MDoc a
- float :: Float -> MDoc a
- double :: Double -> MDoc a
- rational :: Rational -> MDoc a
- semi :: MDoc a
- comma :: MDoc a
- colon :: MDoc a
- space :: MDoc a
- equals :: MDoc a
- lparen :: MDoc a
- rparen :: MDoc a
- lbrack :: MDoc a
- rbrack :: MDoc a
- lbrace :: MDoc a
- rbrace :: MDoc a
- parens :: MDoc a -> MDoc a
- brackets :: MDoc a -> MDoc a
- braces :: MDoc a -> MDoc a
- quotes :: MDoc a -> MDoc a
- doubleQuotes :: MDoc a -> MDoc a
- maybeParens :: Bool -> MDoc a -> MDoc a
- maybeBrackets :: Bool -> MDoc a -> MDoc a
- maybeBraces :: Bool -> MDoc a -> MDoc a
- maybeQuotes :: Bool -> MDoc a -> MDoc a
- maybeDoubleQuotes :: Bool -> MDoc a -> MDoc a
- empty :: MDoc a
- (<>) :: MDoc a -> MDoc a -> MDoc a
- (<+>) :: MDoc a -> MDoc a -> MDoc a
- hcat :: [MDoc a] -> MDoc a
- hsep :: [MDoc a] -> MDoc a
- ($$) :: MDoc a -> MDoc a -> MDoc a
- ($+$) :: MDoc a -> MDoc a -> MDoc a
- vcat :: [MDoc a] -> MDoc a
- sep :: [MDoc a] -> MDoc a
- cat :: [MDoc a] -> MDoc a
- fsep :: [MDoc a] -> MDoc a
- fcat :: [MDoc a] -> MDoc a
- nest :: Int -> MDoc a -> MDoc a
- hang :: MDoc a -> Int -> MDoc a -> MDoc a
- punctuate :: MDoc a -> [MDoc a] -> [MDoc a]
- isEmpty :: MDoc a -> Bool
- first :: MDoc a -> MDoc a -> MDoc a
- reduceDoc :: MDoc a -> RDoc a
- render :: MDoc a -> String
- data Style = Style {
- mode :: Mode
- lineLength :: Int
- ribbonsPerLine :: Float
- style :: Style
- renderStyle :: Style -> MDoc a -> String
- data Mode
- fullRender :: Mode -> Int -> Float -> (TextDetails b -> a -> a) -> a -> MDoc b -> a
- mark :: a -> MDoc a
The document type
The abstract type of documents. An MDoc represents a *set* of layouts. A MDoc with no occurrences of Union or NoDoc represents just one layout.
data TextDetails a Source
The TextDetails data type
A TextDetails represents a fragment of text that will be output at some point.
Chr !Char | A single Char fragment |
Str String | A whole String fragment |
PStr String | Used to represent a Fast String fragment but now deprecated and identical to the Str constructor. |
Mark a |
Eq a => Eq (TextDetails a) | |
Show a => Show (TextDetails a) | |
Generic (TextDetails a) | |
NFData a => NFData (TextDetails a) | |
type Rep (TextDetails a) |
Constructing documents
Converting values into documents
sizedText :: Int -> String -> MDoc a Source
Some text with any width. (text s = sizedText (length s) s
)
zeroWidthText :: String -> MDoc a Source
Some text, but without any width. Use for non-printing text such as a HTML or Latex tags
Simple derived documents
Wrapping documents in delimiters
maybeDoubleQuotes :: Bool -> MDoc a -> MDoc a Source
Apply doubleQuotes
to MDoc
if boolean is true.
Combining documents
($$) :: MDoc a -> MDoc a -> MDoc a infixl 5 Source
Above, except that if the last line of the first argument stops at least one position before the first line of the second begins, these two lines are overlapped. For example:
text "hi" $$ nest 5 (text "there")
lays out as
hi there
rather than
hi there
nest :: Int -> MDoc a -> MDoc a Source
Nest (or indent) a document by a given number of positions
(which may also be negative). nest
satisfies the laws:
nest
0 x = xnest
k (nest
k' x) =nest
(k+k') xnest
k (x<>
y) =nest
k z<>
nest
k ynest
k (x$$
y) =nest
k x$$
nest
k ynest
kempty
=empty
x
, if<>
nest
k y = x<>
yx
non-empty
The side condition on the last law is needed because
empty
is a left identity for <>
.
punctuate :: MDoc a -> [MDoc a] -> [MDoc a] Source
punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
Predicates on documents
Utility functions for documents
first :: MDoc a -> MDoc a -> MDoc a Source
first
returns its first argument if it is non-empty, otherwise its second.
Rendering documents
Default rendering
Rendering with a particular style
A rendering style.
Style | |
|
renderStyle :: Style -> MDoc a -> String Source
Render the MDoc
to a String using the given Style
.
Rendering mode.
PageMode | Normal |
ZigZagMode | With zig-zag cuts |
LeftMode | No indentation, infinitely long lines |
OneLineMode | All on one line |
General rendering
:: Mode | Rendering mode |
-> Int | Line length |
-> Float | Ribbons per line |
-> (TextDetails b -> a -> a) | What to do with text |
-> a | What to do at the end |
-> MDoc b | The document |
-> a | Result |
The general rendering interface.