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

Safe HaskellNone
LanguageHaskell2010

Darcs.Util.Printer

Contents

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

Doc type and structural combinators

newtype Doc Source #

A Doc is a bit of enriched text. Docs are concatenated using <> from class Monoid, which is right-associative.

Constructors

Doc 

Fields

  • unDoc :: St -> Document
     
Instances
IsString Doc Source #

Together with the language extension OverloadedStrings, this allows to use string literals where a Doc is expected.

Instance details

Defined in Darcs.Util.Printer

Methods

fromString :: String -> Doc #

Semigroup Doc Source # 
Instance details

Defined in Darcs.Util.Printer

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Monoid Doc Source #

mappend (<>) is concatenation, mempty is the empty Doc

Instance details

Defined in Darcs.Util.Printer

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

empty :: Doc Source #

The empty Doc

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

(<?>) :: 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 b with a space in between if both are non-empty

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

a $$ b is a above b

vcat :: [Doc] -> Doc Source #

Pile Docs vertically

vsep :: [Doc] -> Doc Source #

Pile Docs vertically, with a blank line in between

hcat :: [Doc] -> Doc Source #

Concatenate Docs horizontally

hsep :: [Doc] -> Doc Source #

Concatenate Docs horizontally with a space as separator

minus :: Doc Source #

A Doc representing a "-"

newline :: Doc Source #

A Doc representing a newline

plus :: Doc Source #

A Doc representing a "+"

space :: Doc Source #

A Doc representing a space (" ")

backslash :: Doc Source #

A Doc representing a "\"

lparen :: Doc Source #

A Doc that represents "("

rparen :: Doc Source #

A Doc that represents ")"

parens :: Doc -> Doc Source #

parens d = lparen <> d <> rparen

Constructing Docs

text :: String -> Doc Source #

text creates a Doc from a String, using printable.

hiddenText :: String -> Doc Source #

hiddenText creates a Doc containing hidden text from a String

invisibleText :: String -> Doc Source #

invisibleText creates a Doc containing invisible text from a String

wrapText :: Int -> String -> Doc Source #

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

quoted :: String -> Doc Source #

Quote a string for screen output

userchunk :: String -> Doc Source #

userchunk creates a Doc containing a user chunk from a String

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.

Rrrright. And what, please is that supposed to mean?

Rendering to String

renderString :: Doc -> String Source #

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

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

renders a Doc into a String using a given set of printers. If content is only available as ByteString, decode according to the current locale.

Rendering to ByteString

renderPS :: Doc -> ByteString Source #

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

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

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

renderPSs :: Doc -> [ByteString] Source #

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

renderPSsWith :: Printers' -> 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.

Printers

data Printers' Source #

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

Constructors

Printers 

type Printer = Printable -> St -> Document Source #

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

Printables

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 

printable :: Printable -> Doc Source #

Creates a Doc from any Printable.

invisiblePrintable :: Printable -> Doc Source #

Creates an invisible Doc from any Printable.

hiddenPrintable :: Printable -> Doc Source #

Creates a hidden Doc from any Printable.

userchunkPrintable :: Printable -> Doc Source #

Creates... WTF is a userchunk???

Constructing colored Docs

data Color Source #

Constructors

Blue 
Red 
Green 
Cyan 
Magenta 

colorText :: Color -> String -> Doc Source #

colorText creates a Doc containing colored text from a String

IO, uses hPut for output

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

hputDoc puts a Doc on the given handle using simplePrinters

hPutDocLn :: Handle -> Doc -> IO () Source #

hputDocLn puts a Doc, followed by a newline 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 -> Handle -> Doc -> IO () Source #

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

hPutDocLnWith :: Printers -> 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 :: Handle -> Doc -> IO () Source #

like hPutDoc but with compress data before writing

debugDocLn :: Doc -> IO () Source #

Write a Doc to stderr if debugging is turned on.

ePutDocLn :: Doc -> IO () Source #

eputDocLn puts a Doc, followed by a newline to stderr using simplePrinters. Like putDocLn, it encodes with the user's locale. This function is the recommended way to output messages that should be visible to users on the console, but cannot (or should not) be silenced even when --quiet is in effect.

errorDoc :: Doc -> a Source #

Fail with a stack trace and the given Doc as error message.

TODO: It is unclear what is unsafe about these constructors

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.