darcs-2.10.0: a distributed, interactive, smart revision control system

Safe HaskellNone
LanguageHaskell2010

Darcs.Util.Printer

Description

A Document is at heart ShowS from the prelude

Essentially, if you give a Doc a string it'll print out whatever it wants followed by that string. So text "foo" makes the Doc that prints "foo" followed by its argument. The combinator names are taken from HughesPJ, although the behaviour of the two libraries is slightly different.

The advantage of Printer over simple string appending/concatenating is that the appends end up associating to the right, e.g.:

  (text "foo" <> text "bar") <> (text "baz" <> text "quux") ""
= \s -> (text "foo" <> text "bar") ((text "baz" <> text "quux") s) ""
= (text "foo" <> text "bar") ((text "baz" <> text "quux") "")
= (\s -> (text "foo") (text "bar" s)) ((text "baz" <> text "quux") "")
= text "foo" (text "bar" ((text "baz" <> text "quux") ""))
= (\s -> "foo" ++ s) (text "bar" ((text "baz" <> text "quux") ""))
= "foo" ++ (text "bar" ((text "baz" <> text "quux") ""))
= "foo" ++ ("bar" ++ ((text "baz" <> text "quux") ""))
= "foo" ++ ("bar" ++ ((\s -> text "baz" (text "quux" s)) ""))
= "foo" ++ ("bar" ++ (text "baz" (text "quux" "")))
= "foo" ++ ("bar" ++ ("baz" ++ (text "quux" "")))
= "foo" ++ ("bar" ++ ("baz" ++ ("quux" ++ "")))

The Empty alternative comes in because you want

text "a" $$ vcat xs $$ text "b"

$$ means above, vcat is the list version of $$ (to be "a\nb" when xs is []), but without the concept of an Empty Document each $$ would add a '\n' and you'd end up with "a\n\nb". Note that Empty /= text "" (the latter would cause two '\\n').

This code was made generic in the element type by Juliusz Chroboczek.

Synopsis

Documentation

data Printable Source

A Printable is either a String, a packed string, or a chunk of text with both representations.

Constructors

S !String 
PS !ByteString 
Both !String !ByteString 

newtype Doc Source

a Doc is a bit of enriched text. Docs get concatanated using <>, which is right-associative.

Constructors

Doc 

Fields

unDoc :: St -> Document
 

Instances

data Printers' Source

A set of printers to print different types of text to a handle.

Constructors

Printers 

type Printer = Printable -> St -> Document Source

data Color Source

Constructors

Blue 
Red 
Green 
Cyan 
Magenta 

data RenderMode Source

Used when rendering a Doc to indicate if the result should be encoded to the current locale or left alone. In practice this only affects output when a relevant DARCS_DONT_ESCAPE_XXX option is set (see Darcs.Util.Printer.Color) If in doubt, choose Standard.

Constructors

Encode

Encode Strings with the current locale. At present ByteStrings are assumed to be in UTF8 and are left alone, so will be mis-encoded in non-UTF8 locales.

Standard

Don't encode.

hPutDoc :: RenderMode -> Handle -> Doc -> IO () Source

hputDoc puts a doc on the given handle using simplePrinters

putDoc :: Doc -> IO () Source

putDoc puts a doc on stdout using the simple printer simplePrinters.

putDocLn :: Doc -> IO () Source

putDocLn puts a doc, followed by a newline on stdout using simplePrinters

hPutDocWith :: Printers -> RenderMode -> Handle -> Doc -> IO () Source

hputDocWith puts a doc on the given handle using the given printer.

hPutDocLnWith :: Printers -> RenderMode -> Handle -> Doc -> IO () Source

hputDocLnWith puts a doc, followed by a newline on the given handle using the given printer.

putDocWith :: Printers -> Doc -> IO () Source

putDocWith puts a doc on stdout using the given printer.

putDocLnWith :: Printers -> Doc -> IO () Source

putDocLnWith puts a doc, followed by a newline on stdout using the given printer.

hPutDocCompr :: RenderMode -> Handle -> Doc -> IO () Source

like hPutDoc but with compress data before writing

renderString :: RenderMode -> Doc -> String Source

renders a Doc into a String with control codes for the special features of the doc.

renderStringWith :: Printers' -> RenderMode -> Doc -> String Source

renders a Doc into a String using a given set of printers.

renderPS :: RenderMode -> Doc -> ByteString Source

renders a Doc into ByteString with control codes for the special features of the Doc. See also readerString.

renderPSWith :: Printers' -> RenderMode -> Doc -> ByteString Source

renders a doc into a ByteString using a given set of printers.

renderPSs :: RenderMode -> Doc -> [ByteString] Source

renders a Doc into a list of PackedStrings, one for each line.

renderPSsWith :: Printers' -> RenderMode -> Doc -> [ByteString] Source

renders a Doc into a list of PackedStrings, one for each chunk of text that was added to the doc, using the given set of printers.

colorText :: Color -> String -> Doc Source

colorText creates a Doc containing colored text from a String

invisibleText :: String -> Doc Source

invisibleText creates a Doc containing invisible text from a String

hiddenText :: String -> Doc Source

hiddenText creates a Doc containing hidden text from a String

userchunk :: String -> Doc Source

userchunk creates a Doc containing a user chunk from a String

text :: String -> Doc Source

text creates a Doc from a String, using printable.

printable :: Printable -> Doc Source

'printable x' creates a Doc from any Printable.

wrapText :: Int -> String -> Doc Source

wrapText n s is a Doc representing s line-wrapped at n characters

blueText :: String -> Doc Source

blueText creates a Doc containing blue text from a String

redText :: String -> Doc Source

blueText creates a Doc containing blue text from a String

greenText :: String -> Doc Source

blueText creates a Doc containing blue text from a String

magentaText :: String -> Doc Source

blueText creates a Doc containing blue text from a String

cyanText :: String -> Doc Source

blueText creates a Doc containing blue text from a String

unsafeText :: String -> Doc Source

unsafeText creates a Doc from a String, using simplePrinter directly

unsafeBoth :: String -> ByteString -> Doc Source

unsafeBoth builds a Doc from a String and a ByteString representing the same text, but does not check that they do.

unsafeBothText :: String -> Doc Source

unsafeBothText builds a Doc from a String. The string is stored in the Doc as both a String and a ByteString.

unsafeChar :: Char -> Doc Source

unsafeChar creates a Doc containing just one character.

invisiblePS :: ByteString -> Doc Source

invisiblePS creates a Doc with invisible text from a ByteString

userchunkPS :: ByteString -> Doc Source

userchunkPS creates a Doc representing a user chunk from a ByteString.

simplePrinters :: Printers Source

simplePrinters is a Printers which uses the set 'simplePriners\'' on any handle.

invisiblePrinter :: Printer Source

invisiblePrinter is the Printer for hidden text. It just replaces the document with empty. It's useful to have a printer that doesn't actually do anything because this allows you to have tunable policies, for example, only printing some text if it's to the terminal, but not if it's to a file or vice-versa.

simplePrinter :: Printer Source

simplePrinter is the simplest Printer: it just concatenates together the pieces of the Doc

empty :: Doc Source

The empty Doc.

(<>) :: Doc -> Doc -> Doc infixr 6 Source

'(<>)' is the concatenation operator for Docs

(<?>) :: Doc -> Doc -> Doc Source

a <?> b is a <> b if a is not empty, else empty.

(<+>) :: Doc -> Doc -> Doc infixr 6 Source

a <+> b is a followed by a space, then b.

($$) :: Doc -> Doc -> Doc infixr 5 Source

a $$ b is a above b.

vcat :: [Doc] -> Doc Source

vcat piles vertically a list of Docs.

vsep :: [Doc] -> Doc Source

vsep piles vertically a list of Docs leaving a blank line between each.

hcat :: [Doc] -> Doc Source

hcat concatenates (horizontally) a list of Docs

minus :: Doc Source

Minimal Docs representing the common characters space, newline minus, plus, and backslash.

newline :: Doc Source

Minimal Docs representing the common characters space, newline minus, plus, and backslash.

plus :: Doc Source

Minimal Docs representing the common characters space, newline minus, plus, and backslash.

space :: Doc Source

Minimal Docs representing the common characters space, newline minus, plus, and backslash.

backslash :: Doc Source

Minimal Docs representing the common characters space, newline minus, plus, and backslash.

lparen :: Doc Source

lparen is the Doc that represents "("

rparen :: Doc Source

rparen is the Doc that represents ")"

parens :: Doc -> Doc Source

parens doc returns a Doc with the content of doc put within a pair of parenthesis.