| Portability | portable |
|---|---|
| Stability | experimental |
| Maintainer | Hans Hoglund <hans@hanshoglund.se> |
| Safe Haskell | Safe-Inferred |
Text.Pretty
Contents
Description
This library was based on The Design of a Pretty-printing Library by Jeuring and Meijer.
Heavily modified by Simon Peyton Jones (December 1996).
Lightly modified by Hans Hoglund (October 2012).
- class Pretty a where
- pretty :: a -> Printer
- prettyList :: [a] -> Printer
- data Printer
- char :: Char -> Printer
- string :: String -> Printer
- sizedText :: Int -> String -> Printer
- zeroWidthText :: String -> Printer
- int :: Int -> Printer
- integer :: Integer -> Printer
- float :: Float -> Printer
- double :: Double -> Printer
- rational :: Rational -> Printer
- empty :: Printer
- (<->) :: Printer -> Printer -> Printer
- (<+>) :: Printer -> Printer -> Printer
- hcat :: [Printer] -> Printer
- hsep :: [Printer] -> Printer
- (</>) :: Printer -> Printer -> Printer
- (<//>) :: Printer -> Printer -> Printer
- vcat :: [Printer] -> Printer
- sep :: [Printer] -> Printer
- cat :: [Printer] -> Printer
- fsep :: [Printer] -> Printer
- fcat :: [Printer] -> Printer
- wrap :: Char -> Char -> Printer -> Printer
- parens :: Printer -> Printer
- brackets :: Printer -> Printer
- braces :: Printer -> Printer
- quotes :: Printer -> Printer
- doubleQuotes :: Printer -> Printer
- nest :: Int -> Printer -> Printer
- hang :: Printer -> Int -> Printer -> Printer
- sepBy :: Printer -> [Printer] -> Printer
- initBy :: Printer -> [Printer] -> Printer
- termBy :: Printer -> [Printer] -> Printer
- sepByS :: Printer -> [Printer] -> Printer
- initByS :: Printer -> [Printer] -> Printer
- termByS :: Printer -> [Printer] -> Printer
- isEmpty :: Printer -> Bool
- runPrinter :: Printer -> String
- data Mode
- = PageMode
- | ZigZagMode
- | LeftMode
- | OneLineMode
- data Style = Style {
- mode :: Mode
- lineLength :: Int
- ribbonsPerLine :: Float
- style :: Style
- runPrinterStyle :: Style -> Printer -> String
The Pretty typeclass
Class of types that can be pretty-printed.
The Pretty class is similar to Show, but converts values to Printers instead
of Strings. A printer is essentially a string with some extra structural information
such as length and indentation.
Note that the instances for primitive types, lists and tuples all satisfy
(show . pretty) x == show x
Methods
Return a printer for the given value.
prettyList :: [a] -> PrinterSource
The method prettyList is provided to allow the programmer to give a specialised way of printing lists of values. For example, this is used by the predefined Pretty instance of the Char type, where values of type String should be shown in double quotes, rather than between square brackets.
The Printer type
The abstract type of printers.
Construction
Primitive types
sizedText :: Int -> String -> PrinterSource
Some string with any width. (string s = sizedText (length s) s)
zeroWidthText :: String -> PrinterSource
Some string, but without any width. Use for non-printing string such as a HTML or Latex tags
Combinators
(</>) :: Printer -> Printer -> PrinterSource
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:
string "hi" </> nest 5 (string "there")
lays out as
hi there
rather than
hi
there
Wrapping and punctuation
doubleQuotes :: Printer -> PrinterSource
Wrap printer in "..."
nest :: Int -> Printer -> PrinterSource
Nest (or indent) a printer by a given number of positions
(which may also be negative). nest satisfies the laws:
nest0 x = xnestk (nestk' x) =nest(k+k') xnestk (x<>y) =nestk z<>nestk ynestk (x</>y) =nestk x</>nestk ynestkempty=empty-
x, if<>nestk y = x<>yxnon-empty
The side condition on the last law is needed because
empty is a left identity for <>.
sepBy :: Printer -> [Printer] -> PrinterSource
Join with separator.
sepBy q [x1,x2..xn] = x1 <> q <> x2 <> q .. xn.
initBy :: Printer -> [Printer] -> PrinterSource
Join with initiator.
initBy q [x1,x2..xn] = q <> x1 <> q <> x2 <> q .. xn.
termBy :: Printer -> [Printer] -> PrinterSource
Join with terminator.
termBy q [x1,x2..xn] = x1 <> q <> x2 <> q .. xn <> q.
sepByS :: Printer -> [Printer] -> PrinterSource
Join with separator followed by space.
sepByS q [x1,x2..xn] = x1 <> q <+> x2 <> q <+>.. xn.
initByS :: Printer -> [Printer] -> PrinterSource
Join with initiator followed by space.
initByS q [x1,x2..xn] = q <+> x1 <> q <+> x2 <> q <+> .. xn.
termByS :: Printer -> [Printer] -> PrinterSource
Join with terminator followed by space.
termByS q [x1,x2..xn] = x1 <> q <+> x2 <> q <+> .. xn <> q.
Predicates on printers
Rendering printers
runPrinter :: Printer -> StringSource
Render the Printer to a String using the default Style.
Rendering mode.
Constructors
| PageMode | Normal |
| ZigZagMode | With zig-zag cuts |
| LeftMode | No indentation, infinitely long lines |
| OneLineMode | All on one line |
A printing style.
Constructors
| Style | |
Fields
| |
runPrinterStyle :: Style -> Printer -> StringSource
Render the Printer to a String using the given Style.