A Document is at heart ShowS from the prelude
\htmladdnormallink{http://www.haskell.org/onlinereport/standard-prelude.html#\$tShowS}
Essentially, if you give a Doc a string it'll print out whatever it
wants followed by that string. So \verb!(text "foo")! makes the Doc that
prints \verb!"foo"! followed by its argument. The combinator names are taken
from Text.PrettyPrint.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.:
\begin{verbatim}
(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" ++ "")))
\end{verbatim}
The Empty alternative comes in because you want
\begin{verbatim}
text "a" $$ vcat xs $$ text "b"
\end{verbatim}
(\verb!$$! means ``above'', vcat is the list version of \verb!$$!) to be
\verb!"a\nb"! when \verb!xs! is \verb![]!, but without the concept of an
Empty Document each \verb!$$! would add a \verb!'\n'! and you'd end up with
\verb!"a\n\nb"!. Note that \verb!Empty /= text ""! (the latter would cause two
\verb!'\n'!s).
This code was made generic in the element type by Juliusz Chroboczek.
\begin{code}
module Printer (Printable(..), Doc(Doc,unDoc), Printers, Printers'(..), Printer, Color(..),
hPutDoc, hPutDocLn, putDoc, putDocLn,
hPutDocWith, hPutDocLnWith, putDocWith, putDocLnWith,
renderString, renderStringWith, renderPS, renderPSWith,
renderPSs, renderPSsWith, lineColor,
prefix, insertBeforeLastline, colorText, invisibleText,
hiddenText, hiddenPrefix, userchunk, text,
printable, wrapText,
blueText, redText, greenText, magentaText, cyanText,
unsafeText, unsafeBoth, unsafeBothText, unsafeChar,
invisiblePS, packedString, unsafePackedString, userchunkPS,
simplePrinters, invisiblePrinter, simplePrinter,
doc, empty, (<>), (<?>), (<+>), ($$), vcat, vsep, hcat,
minus, newline, plus, space, backslash, lparen, rparen,
parens,
errorDoc,
) where
import Data.List (intersperse)
import System.IO (Handle, stdout, hPutStr)
import ByteStringUtils ( linesPS )
import qualified Data.ByteString as B (ByteString, hPut, concat)
import qualified Data.ByteString.Char8 as BC (unpack, pack, singleton)
data Printable = S !String
| PS !B.ByteString
| Both !String !B.ByteString
spaceP :: Printable
spaceP = Both " " (BC.singleton ' ')
newlineP :: Printable
newlineP = S "\n"
space, newline, plus, minus, backslash :: Doc
space = unsafeBoth " " (BC.singleton ' ')
newline = unsafeChar '\n'
minus = unsafeBoth "-" (BC.singleton '-')
plus = unsafeBoth "+" (BC.singleton '+')
backslash = unsafeBoth "\\" (BC.singleton '\\')
lparen :: Doc
lparen = unsafeBoth "(" (BC.singleton '(')
rparen :: Doc
rparen = unsafeBoth ")" (BC.singleton ')')
parens :: Doc -> Doc
parens d = lparen <> d <> rparen
errorDoc :: Doc -> a
errorDoc = error . renderStringWith simplePrinters'
putDocWith :: Printers -> Doc -> IO ()
putDocWith prs = hPutDocWith prs stdout
putDocLnWith :: Printers -> Doc -> IO ()
putDocLnWith prs = hPutDocLnWith prs stdout
putDoc :: Doc -> IO ()
putDocLn :: Doc -> IO ()
putDoc = hPutDoc stdout
putDocLn = hPutDocLn stdout
hPutDocWith :: Printers -> Handle -> Doc -> IO ()
hPutDocLnWith :: Printers -> Handle -> Doc -> IO ()
hPutDocWith prs h d = hPrintPrintables h (renderWith (prs h) d)
hPutDocLnWith prs h d = hPutDocWith prs h (d <?> newline)
hPutDoc :: Handle -> Doc -> IO ()
hPutDocLn :: Handle -> Doc -> IO ()
hPutDoc = hPutDocWith simplePrinters
hPutDocLn = hPutDocLnWith simplePrinters
hPrintPrintables :: Handle -> [Printable] -> IO ()
hPrintPrintables h = mapM_ (hPrintPrintable h)
hPrintPrintable :: Handle -> Printable -> IO ()
hPrintPrintable h (S ps) = hPutStr h ps
hPrintPrintable h (PS ps) = B.hPut h ps
hPrintPrintable h (Both _ ps) = B.hPut h ps
newtype Doc = Doc { unDoc :: St -> Document }
data St = St { printers :: !Printers',
currentPrefix :: !([Printable] -> [Printable]) }
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
data Color = Blue | Red | Green | Cyan | Magenta
data Document = Document ([Printable] -> [Printable])
| Empty
renderString :: Doc -> String
renderString = renderStringWith simplePrinters'
renderStringWith :: Printers' -> Doc -> String
renderStringWith prs d = concatMap toString $ renderWith prs d
where toString (S s) = s
toString (PS ps) = BC.unpack ps
toString (Both s _) = s
renderPS :: Doc -> B.ByteString
renderPS = renderPSWith simplePrinters'
renderPSs :: Doc -> [B.ByteString]
renderPSs = renderPSsWith simplePrinters'
renderPSWith :: Printers' -> Doc -> B.ByteString
renderPSWith prs d = B.concat $ renderPSsWith prs d
renderPSsWith :: Printers' -> Doc -> [B.ByteString]
renderPSsWith prs d = map toPS $ renderWith prs d
where toPS (S s) = BC.pack s
toPS (PS ps) = ps
toPS (Both _ ps) = ps
renderWith :: Printers' -> Doc -> [Printable]
renderWith ps (Doc d) = case d (initState ps) of
Empty -> []
Document f -> f []
initState :: Printers' -> St
initState prs = St { printers = prs, currentPrefix = id }
prefix :: String -> Doc -> Doc
prefix s (Doc d) = Doc $ \st ->
let p = S s
st' = st { currentPrefix = currentPrefix st . (p:) } in
case d st' of
Document d'' -> Document $ (p:) . d''
Empty -> Empty
insertBeforeLastline :: Doc -> Doc -> Doc
insertBeforeLastline a b =
case reverse $ map packedString $ linesPS $ renderPS a of
(ll:ls) -> vcat (reverse ls) $$ b $$ ll
[] -> error "empty Doc given as first argument of Printer.insert_before_last_line"
lineColor :: Color -> Doc -> Doc
lineColor c d = Doc $ \st -> case lineColorT (printers st) c d of
Doc d' -> d' st
hiddenPrefix :: String -> Doc -> Doc
hiddenPrefix s (Doc d) =
Doc $ \st -> let pr = printers st
p = S (renderStringWith pr $ hiddenText s)
st' = st { currentPrefix = currentPrefix st . (p:) }
in case d st' of
Document d'' -> Document $ (p:) . d''
Empty -> Empty
unsafeBoth :: String -> B.ByteString -> Doc
unsafeBoth s ps = Doc $ simplePrinter (Both s ps)
unsafeBothText :: String -> Doc
unsafeBothText s = Doc $ simplePrinter (Both s (BC.pack s))
packedString :: B.ByteString -> Doc
unsafePackedString :: B.ByteString -> Doc
invisiblePS :: B.ByteString -> Doc
userchunkPS :: B.ByteString -> Doc
packedString = printable . PS
unsafePackedString = Doc . simplePrinter . PS
invisiblePS = invisiblePrintable . PS
userchunkPS = userchunkPrintable . PS
unsafeChar :: Char -> Doc
unsafeChar = unsafeText . (:"")
text :: String -> Doc
unsafeText :: String -> Doc
invisibleText :: String -> Doc
hiddenText :: String -> Doc
userchunk :: String -> Doc
blueText, redText, greenText, magentaText, cyanText :: String -> Doc
text = printable . S
unsafeText = Doc . simplePrinter . S
invisibleText = invisiblePrintable . S
hiddenText = hiddenPrintable . S
userchunk = userchunkPrintable . S
blueText = colorText Blue
redText = colorText Red
greenText = colorText Green
magentaText = colorText Magenta
cyanText = colorText Cyan
colorText :: Color -> String -> Doc
colorText c = mkColorPrintable c . S
wrapText :: Int -> String -> Doc
wrapText n s =
vcat $ map text $ reverse $ "": (foldl add_to_line [] $ words s)
where add_to_line [] a = [a]
add_to_line ("":d) a = (a:d)
add_to_line (l:ls) new | length l + length new > n = new:l:ls
add_to_line (l:ls) new = (l ++ " " ++ new):ls
printable, invisiblePrintable, hiddenPrintable, userchunkPrintable :: Printable -> Doc
printable x = Doc $ \st -> defP (printers st) x st
mkColorPrintable :: Color -> Printable -> Doc
mkColorPrintable c x = Doc $ \st -> colorP (printers st) c x st
invisiblePrintable x = Doc $ \st -> invisibleP (printers st) x st
hiddenPrintable x = Doc $ \st -> hiddenP (printers st) x st
userchunkPrintable x = Doc $ \st -> userchunkP (printers st) x st
simplePrinters :: Printers
simplePrinters _ = simplePrinters'
simplePrinters' :: Printers'
simplePrinters' = Printers { colorP = const simplePrinter,
invisibleP = simplePrinter,
hiddenP = invisiblePrinter,
userchunkP = simplePrinter,
defP = simplePrinter,
lineColorT = const id,
lineColorS = id
}
simplePrinter :: Printer
invisiblePrinter :: Printer
simplePrinter x = unDoc $ doc (\s -> x:s)
invisiblePrinter _ = unDoc empty
infixr 6 <>
infixr 6 <+>
infixr 5 $$
empty :: Doc
empty = Doc $ const Empty
doc :: ([Printable] -> [Printable]) -> Doc
doc f = Doc $ const $ Document f
(<>) :: Doc -> Doc -> Doc
(<?>) :: Doc -> Doc -> Doc
(<+>) :: Doc -> Doc -> Doc
($$) :: Doc -> Doc -> Doc
Doc a <> Doc b =
Doc $ \st -> case a st of
Empty -> b st
Document af ->
Document (\s -> af $ case b st of
Empty -> s
Document bf -> bf s)
Doc a <?> Doc b =
Doc $ \st -> case a st of
Empty -> Empty
Document af -> Document (\s -> af $ case b st of
Empty -> s
Document bf -> bf s)
Doc a <+> Doc b =
Doc $ \st -> case a st of
Empty -> b st
Document af -> Document (\s -> af $ case b st of
Empty -> s
Document bf ->
spaceP:bf s)
Doc a $$ Doc b =
Doc $ \st -> case a st of
Empty -> b st
Document af ->
Document (\s -> af $ case b st of
Empty -> s
Document bf -> sf (newlineP:pf (bf s)))
where pf = currentPrefix st
sf = lineColorS $ printers st
vcat :: [Doc] -> Doc
vcat [] = empty
vcat ds = foldr1 ($$) ds
vsep :: [Doc] -> Doc
vsep [] = empty
vsep ds = foldr1 ($$) $ intersperse (text "") ds
hcat :: [Doc] -> Doc
hcat [] = empty
hcat ds = foldr1 (<>) ds
\end{code}