Copyright | (c) 2008 Utrecht University |
---|---|
License | All rights reserved |
Maintainer | stefan@cs.uu.nl |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
CCO.Printing
Contents
Description
A combinator library for pretty printing.
Inspired by
- S. Doaitse Swierstra, Pablo R. Azero Alcocer, and Joao Saraiva. Designing and implementing combinator languages. In S. Doaitse Swierstra and Pedro Rangel Henriques, and Jose Nuno Oliveira, editors, Advanced Functional Programming, Third International School, Braga, Portugal, September 12-19, 1998, Revised Lectures, volume 1608 of Lecture Notes in Computer Science, pages 150-206. Springer-Verlag, 1999.
- data Doc
- isEmpty :: Doc -> Bool
- empty :: Doc
- text :: String -> Doc
- wrapped :: String -> Doc
- indent :: Int -> Doc -> Doc
- (>-<) :: Doc -> Doc -> Doc
- above :: [Doc] -> Doc
- (>|<) :: Doc -> Doc -> Doc
- besides :: [Doc] -> Doc
- (>//<) :: Doc -> Doc -> Doc
- split :: [Doc] -> Doc
- join :: Doc -> Doc
- (>^<) :: Doc -> Doc -> Doc
- choose :: [Doc] -> Doc
- space :: Doc
- period :: Doc
- comma :: Doc
- semicolon :: Doc
- colon :: Doc
- sepBy :: [Doc] -> Doc -> Doc
- (>#<) :: Doc -> Doc -> Doc
- lparen :: Doc
- rparen :: Doc
- lbracket :: Doc
- rbracket :: Doc
- lbrace :: Doc
- rbrace :: Doc
- langle :: Doc
- rangle :: Doc
- enclose :: Doc -> Doc -> Doc -> Doc
- parens :: Doc -> Doc
- brackets :: Doc -> Doc
- braces :: Doc -> Doc
- angles :: Doc -> Doc
- black :: Doc -> Doc
- red :: Doc -> Doc
- green :: Doc -> Doc
- blue :: Doc -> Doc
- yellow :: Doc -> Doc
- magenta :: Doc -> Doc
- cyan :: Doc -> Doc
- white :: Doc -> Doc
- render :: Int -> Doc -> Maybe String
- render_ :: Int -> Doc -> String
- renderHeight :: Int -> Doc -> Maybe (String, Int)
- renderHeight_ :: Int -> Doc -> (String, Int)
- renderIO :: Int -> Doc -> Maybe (IO ())
- renderIO_ :: Int -> Doc -> IO ()
- renderIOHeight :: Int -> Doc -> Maybe (IO (), Int)
- renderIOHeight_ :: Int -> Doc -> (IO (), Int)
- class Printable a where
- showable :: Show a => a -> Doc
Abstract document type
Primitive document constructors
wrapped :: String -> Doc Source
wrapped txt
produces a document containing the text txt
, possibly
wrapping its contents to fit the available space
Elementary document combinators
(>|<) :: Doc -> Doc -> Doc infixr 3 Source
"Besides": puts two documents next to eachother by "dovetailing" them.
Parallelisation
(>//<) :: Doc -> Doc -> Doc infixr 1 Source
"Split": introduces two alternative ("parallel") formattings.
Introduces multiple alternative formattings:
split = foldr (>//<) empty
.
Selects the most space-efficient of all alternative formattings for a document.
Punctuation
sepBy :: [Doc] -> Doc -> Doc Source
Inserts a delimiter between all adjacent nonempty documents in a list.
(>#<) :: Doc -> Doc -> Doc infixr 3 Source
Inserts a space between two documents.
If one of the documents is empty, the other one is returned:
l >#< r = [l, r] `sepBy` space
.
enclose :: Doc -> Doc -> Doc -> Doc Source
Encloses a document in brackets:
enclose l r d = l >|< d >|< r
.
Encloses a document in square brackets:
brackets = enclose lbracket rbracket
.
Colours
Rendering
render :: Int -> Doc -> Maybe String Source
Tries to render a document within a specified amount of horizontal space.
render_ :: Int -> Doc -> String Source
Tries to render a document within a specified amount of horizontal space. If the document cannot be rendered within the given amount of space, the amount of space is, until the document fits, repeatedly enlarged by 10 percent.
renderHeight :: Int -> Doc -> Maybe (String, Int) Source
Tries to render a document within a specified amount of horizontal space. A resulting rendering is tupled with the number of new lines claimed by the rendering.
renderIO :: Int -> Doc -> Maybe (IO ()) Source
Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel.
renderIO_ :: Int -> Doc -> IO () Source
Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel. If the document cannot be rendered within the given amount of space, the amount of space is, until the document fits, repeatedly enlarged by 10 percent.
renderIOHeight :: Int -> Doc -> Maybe (IO (), Int) Source
Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel. A resulting rendering is tupled with the number of new lines claimed by the rendering.
renderIOHeight_ :: Int -> Doc -> (IO (), Int) Source
Tries to render a document within a specified amount of horizontal space and to print it to the standard output channel. If the document cannot be rendered within the given amount of space, the amount of space is, until the document fits, repeatedly enlarged by 10 percent. The resulting rendering is tupled with the number of new lines claimed by the rendering.
The class Printable
class Printable a where Source
The class Printable
.
Instances of Printable
provide a pretty printer for their values.
A minimal complete definition must supply the method pp
.