Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- newtype Doc = Doc {
- unDoc :: St -> Document
- empty :: Doc
- (<>) :: Monoid m => m -> m -> m
- (<?>) :: Doc -> Doc -> Doc
- (<+>) :: Doc -> Doc -> Doc
- ($$) :: Doc -> Doc -> Doc
- vcat :: [Doc] -> Doc
- vsep :: [Doc] -> Doc
- hcat :: [Doc] -> Doc
- hsep :: [Doc] -> Doc
- minus :: Doc
- newline :: Doc
- plus :: Doc
- space :: Doc
- backslash :: Doc
- lparen :: Doc
- rparen :: Doc
- parens :: Doc -> Doc
- text :: String -> Doc
- hiddenText :: String -> Doc
- invisibleText :: String -> Doc
- wrapText :: Int -> String -> Doc
- quoted :: String -> Doc
- userchunk :: String -> Doc
- packedString :: ByteString -> Doc
- prefix :: String -> Doc -> Doc
- hiddenPrefix :: String -> Doc -> Doc
- insertBeforeLastline :: Doc -> Doc -> Doc
- prefixLines :: Doc -> Doc -> Doc
- invisiblePS :: ByteString -> Doc
- userchunkPS :: ByteString -> Doc
- data RenderMode
- renderString :: RenderMode -> Doc -> String
- renderStringWith :: Printers' -> RenderMode -> Doc -> String
- renderPS :: RenderMode -> Doc -> ByteString
- renderPSWith :: Printers' -> RenderMode -> Doc -> ByteString
- renderPSs :: RenderMode -> Doc -> [ByteString]
- renderPSsWith :: Printers' -> RenderMode -> Doc -> [ByteString]
- type Printers = Handle -> Printers'
- data Printers' = Printers {
- colorP :: !(Color -> Printer)
- invisibleP :: !Printer
- hiddenP :: !Printer
- userchunkP :: !Printer
- defP :: !Printer
- lineColorT :: !(Color -> Doc -> Doc)
- lineColorS :: !([Printable] -> [Printable])
- type Printer = Printable -> St -> Document
- simplePrinters :: Printers
- invisiblePrinter :: Printer
- simplePrinter :: Printer
- data Printable
- = S !String
- | PS !ByteString
- | Both !String !ByteString
- doc :: ([Printable] -> [Printable]) -> Doc
- printable :: Printable -> Doc
- invisiblePrintable :: Printable -> Doc
- hiddenPrintable :: Printable -> Doc
- userchunkPrintable :: Printable -> Doc
- data Color
- blueText :: String -> Doc
- redText :: String -> Doc
- greenText :: String -> Doc
- magentaText :: String -> Doc
- cyanText :: String -> Doc
- colorText :: Color -> String -> Doc
- lineColor :: Color -> Doc -> Doc
- hPutDoc :: RenderMode -> Handle -> Doc -> IO ()
- hPutDocLn :: RenderMode -> Handle -> Doc -> IO ()
- putDoc :: Doc -> IO ()
- putDocLn :: Doc -> IO ()
- hPutDocWith :: Printers -> RenderMode -> Handle -> Doc -> IO ()
- hPutDocLnWith :: Printers -> RenderMode -> Handle -> Doc -> IO ()
- putDocWith :: Printers -> Doc -> IO ()
- putDocLnWith :: Printers -> Doc -> IO ()
- hPutDocCompr :: RenderMode -> Handle -> Doc -> IO ()
- debugDocLn :: Doc -> IO ()
- ePutDocLn :: Doc -> IO ()
- errorDoc :: Doc -> a
- unsafeText :: String -> Doc
- unsafeBoth :: String -> ByteString -> Doc
- unsafeBothText :: String -> Doc
- unsafeChar :: Char -> Doc
- unsafePackedString :: ByteString -> Doc
Doc
type and structural combinators
Constructing Doc
s
invisibleText :: String -> Doc Source #
invisibleText
creates a Doc
containing invisible text from a String
packedString :: ByteString -> Doc Source #
packedString
builds a Doc
from a ByteString
using printable
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
data RenderMode Source #
renderString :: RenderMode -> Doc -> String Source #
renderStringWith :: Printers' -> RenderMode -> Doc -> String Source #
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.
Printers
A set of printers to print different types of text to a handle.
Printers | |
|
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
A Printable
is either a String, a packed string, or a chunk of
text with both representations.
S !String | |
PS !ByteString | |
Both !String !ByteString |
userchunkPrintable :: Printable -> Doc Source #
Creates... WTF is a userchunk???
Constructing colored Doc
s
magentaText :: String -> Doc Source #
IO
hPutDoc :: RenderMode -> Handle -> Doc -> IO () Source #
hputDoc
puts a doc on the given handle using simplePrinters
hPutDocLn :: RenderMode -> Handle -> Doc -> IO () Source #
hputDocLn
puts a doc, followed by a newline on the given handle using
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
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.
Unsafe 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.
unsafePackedString :: ByteString -> Doc Source #
unsafePackedString
builds a Doc
from a ByteString
using simplePrinter