module Darcs.Util.Printer
(
Doc(Doc,unDoc)
, empty, (<>), (<?>), (<+>), ($$), ($+$), vcat, vsep, hcat, hsep
, minus, newline, plus, space, backslash, lparen, rparen
, parens, sentence
, text
, hiddenText
, invisibleText
, wrapText, quoted
, formatText
, formatWords
, pathlist
, userchunk, packedString
, prefix
, hiddenPrefix
, insertBeforeLastline
, prefixLines
, invisiblePS, userchunkPS
, renderString, renderStringWith
, renderPS, renderPSWith
, renderPSs, renderPSsWith
, Printers
, Printers'(..)
, Printer
, simplePrinters, invisiblePrinter, simplePrinter
, Printable(..)
, doc
, printable, invisiblePrintable, hiddenPrintable, userchunkPrintable
, Color(..)
, blueText, redText, greenText, magentaText, cyanText
, colorText
, lineColor
, hPutDoc, hPutDocLn, putDoc, putDocLn
, hPutDocWith, hPutDocLnWith, putDocWith, putDocLnWith
, hPutDocCompr
, debugDocLn
, unsafeText, unsafeBoth, unsafeBothText, unsafeChar
, unsafePackedString
) where
import Darcs.Prelude
import Data.String ( IsString(..) )
import System.IO ( Handle, stdout )
import qualified Data.ByteString as B ( ByteString, hPut, concat )
import qualified Data.ByteString.Char8 as BC ( singleton )
import Darcs.Util.ByteString ( linesPS, decodeLocale, encodeLocale, gzWriteHandle )
import Darcs.Util.Global ( debugMessage )
data Printable = S !String
| PS !B.ByteString
| Both !String !B.ByteString
spaceP :: Printable
spaceP = Both " " (BC.singleton ' ')
newlineP :: Printable
newlineP = S "\n"
space :: Doc
space = unsafeBoth " " (BC.singleton ' ')
newline :: Doc
newline = unsafeChar '\n'
minus :: Doc
minus = unsafeBoth "-" (BC.singleton '-')
plus :: Doc
plus = unsafeBoth "+" (BC.singleton '+')
backslash :: Doc
backslash = unsafeBoth "\\" (BC.singleton '\\')
lparen :: Doc
lparen = unsafeBoth "(" (BC.singleton '(')
rparen :: Doc
rparen = unsafeBoth ")" (BC.singleton ')')
parens :: Doc -> Doc
parens d = lparen <> d <> rparen
sentence :: Doc -> Doc
sentence = (<> text ".")
pathlist :: [FilePath] -> Doc
pathlist paths = hsep (map quoted paths)
putDocWith :: Printers -> Doc -> IO ()
putDocWith prs = hPutDocWith prs stdout
putDocLnWith :: Printers -> Doc -> IO ()
putDocLnWith prs = hPutDocLnWith prs stdout
putDoc :: Doc -> IO ()
putDoc = hPutDoc stdout
putDocLn :: Doc -> IO ()
putDocLn = hPutDocLn stdout
hPutDocWith :: Printers -> Handle -> Doc -> IO ()
hPutDocWith prs h d = do
p <- prs h
hPrintPrintables h (renderWith p d)
hPutDocLnWith :: Printers -> Handle -> Doc -> IO ()
hPutDocLnWith prs h d = hPutDocWith prs h (d <?> newline)
hPutDoc :: Handle -> Doc -> IO ()
hPutDoc = hPutDocWith simplePrinters
hPutDocLn :: Handle -> Doc -> IO ()
hPutDocLn = hPutDocLnWith simplePrinters
hPutDocCompr :: Handle -> Doc -> IO ()
hPutDocCompr h = gzWriteHandle h . renderPSs
debugDocLn :: Doc -> IO ()
debugDocLn = debugMessage . renderString
hPrintPrintables :: Handle -> [Printable] -> IO ()
hPrintPrintables h = mapM_ (hPrintPrintable h)
hPrintPrintable :: Handle -> Printable -> IO ()
hPrintPrintable h (S ps) = B.hPut h (encodeLocale ps)
hPrintPrintable h (PS ps) = B.hPut h ps
hPrintPrintable h (Both _ ps) = B.hPut h ps
newtype Doc = Doc { unDoc :: St -> Document }
instance IsString Doc where
fromString = text
data St = St { printers :: !Printers',
currentPrefix :: !([Printable] -> [Printable]) }
type Printers = Handle -> IO 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) = decodeLocale 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) = encodeLocale 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
prefixLines :: Doc -> Doc -> Doc
prefixLines prefixer prefixee =
vcat $ map (prefixer <+>) $ map packedString $ linesPS $ renderPS prefixee
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 (encodeLocale s))
packedString :: B.ByteString -> Doc
packedString = printable . PS
unsafePackedString :: B.ByteString -> Doc
unsafePackedString = Doc . simplePrinter . PS
invisiblePS :: B.ByteString -> Doc
invisiblePS = invisiblePrintable . PS
userchunkPS :: B.ByteString -> Doc
userchunkPS = userchunkPrintable . PS
unsafeChar :: Char -> Doc
unsafeChar = unsafeText . (:"")
text :: String -> Doc
text = printable . S
unsafeText :: String -> Doc
unsafeText = Doc . simplePrinter . S
invisibleText :: String -> Doc
invisibleText = invisiblePrintable . S
hiddenText :: String -> Doc
hiddenText = hiddenPrintable . S
userchunk :: String -> Doc
userchunk = userchunkPrintable . S
blueText, redText, greenText, magentaText, cyanText :: String -> Doc
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
formatText :: Int -> [String] -> Doc
formatText w = vsep . map (wrapText w)
formatWords :: [String] -> Doc
formatWords = wrapText 80 . unwords
printable :: 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 :: Printable -> Doc
invisiblePrintable x = Doc $ \st -> invisibleP (printers st) x st
hiddenPrintable :: Printable -> Doc
hiddenPrintable x = Doc $ \st -> hiddenP (printers st) x st
userchunkPrintable :: Printable -> Doc
userchunkPrintable x = Doc $ \st -> userchunkP (printers st) x st
simplePrinters :: Printers
simplePrinters _ = return simplePrinters'
simplePrinters' :: Printers'
simplePrinters' = Printers { colorP = const simplePrinter,
invisibleP = simplePrinter,
hiddenP = invisiblePrinter,
userchunkP = simplePrinter,
defP = simplePrinter,
lineColorT = const id,
lineColorS = id
}
simplePrinter :: Printer
simplePrinter x = unDoc $ doc (\s -> x:s)
invisiblePrinter :: Printer
invisiblePrinter _ = unDoc empty
infixr 6 `append`
infixr 6 <+>
infixr 5 $+$
infixr 5 $$
empty :: Doc
empty = Doc $ const Empty
doc :: ([Printable] -> [Printable]) -> Doc
doc f = Doc $ const $ Document f
instance Semigroup Doc where
(<>) = append
instance Monoid Doc where
mempty = empty
mappend = append
append :: Doc -> Doc -> Doc
Doc a `append` 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 -> Doc -> Doc
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 -> 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 ->
spaceP:bf s)
($$) :: 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 -> sf (newlineP:pf (bf s)))
where pf = currentPrefix st
sf = lineColorS $ printers st
($+$) :: 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 -> sf (newlineP:newlineP:pf (bf s)))
where pf = currentPrefix st
sf = lineColorS $ printers st
vcat :: [Doc] -> Doc
vcat = foldr ($$) empty
vsep :: [Doc] -> Doc
vsep = foldr ($+$) empty
hcat :: [Doc] -> Doc
hcat = mconcat
hsep :: [Doc] -> Doc
hsep = foldr (<+>) empty
quoted :: String -> Doc
quoted s = text "\"" <> text (escape s) <> text "\""
where
escape "" = ""
escape (c:cs) = if c `elem` ['\\', '"']
then '\\' : c : escape cs
else c : escape cs