module Text.PrettyPrint.ANSI.Leijen (
Doc, putDoc, hPutDoc,
empty, char, text, (<>), nest, line, linebreak, group, softline,
softbreak, hardline, flatAlt, renderSmart,
align, hang, indent, encloseSep, list, tupled, semiBraces,
(<+>), (<$>), (</>), (<$$>), (<//>),
hsep, vsep, fillSep, sep, hcat, vcat, fillCat, cat, punctuate,
fill, fillBreak,
enclose, squotes, dquotes, parens, angles, braces, brackets,
lparen, rparen, langle, rangle, lbrace, rbrace, lbracket, rbracket,
squote, dquote, semi, colon, comma, space, dot, backslash, equals,
black, red, green, yellow, blue, magenta, cyan, white,
dullblack, dullred, dullgreen, dullyellow, dullblue, dullmagenta, dullcyan, dullwhite,
onblack, onred, ongreen, onyellow, onblue, onmagenta, oncyan, onwhite,
ondullblack, ondullred, ondullgreen, ondullyellow, ondullblue, ondullmagenta, ondullcyan, ondullwhite,
bold, debold,
underline, deunderline,
plain,
string, int, integer, float, double, rational,
Pretty(..),
SimpleDoc(..), renderPretty, renderCompact, displayS, displayIO
, bool
, column, columns, nesting, width
) where
import System.IO (Handle,hPutStr,hPutChar,stdout)
import System.Console.ANSI (Color(..), ColorIntensity(..), ConsoleLayer(..),
Underlining(..), ConsoleIntensity(..),
SGR(..), hSetSGR, setSGRCode)
import Data.String (IsString(..))
import Data.Maybe (catMaybes)
import Data.Monoid (Monoid, mappend, mconcat, mempty)
infixr 5 </>,<//>,<$>,<$$>
infixr 6 <>,<+>
list :: [Doc] -> Doc
list = encloseSep lbracket rbracket comma
tupled :: [Doc] -> Doc
tupled = encloseSep lparen rparen comma
semiBraces :: [Doc] -> Doc
semiBraces = encloseSep lbrace rbrace semi
encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc
encloseSep left right sep ds
= case ds of
[] -> left <> right
[d] -> left <> d <> right
_ -> align (cat (zipWith (<>) (left : repeat sep) ds) <> right)
punctuate :: Doc -> [Doc] -> [Doc]
punctuate p [] = []
punctuate p [d] = [d]
punctuate p (d:ds) = (d <> p) : punctuate p ds
sep :: [Doc] -> Doc
sep = group . vsep
fillSep :: [Doc] -> Doc
fillSep = fold (</>)
hsep :: [Doc] -> Doc
hsep = fold (<+>)
vsep :: [Doc] -> Doc
vsep = fold (<$>)
cat :: [Doc] -> Doc
cat = group . vcat
fillCat :: [Doc] -> Doc
fillCat = fold (<//>)
hcat :: [Doc] -> Doc
hcat = fold (<>)
vcat :: [Doc] -> Doc
vcat = fold (<$$>)
fold :: (Doc -> Doc -> Doc) -> [Doc] -> Doc
fold f [] = empty
fold f ds = foldr1 f ds
(<>) :: Doc -> Doc -> Doc
x <> y = x `beside` y
(<+>) :: Doc -> Doc -> Doc
x <+> y = x <> space <> y
(</>) :: Doc -> Doc -> Doc
x </> y = x <> softline <> y
(<//>) :: Doc -> Doc -> Doc
x <//> y = x <> softbreak <> y
(<$>) :: Doc -> Doc -> Doc
x <$> y = x <> line <> y
(<$$>) :: Doc -> Doc -> Doc
x <$$> y = x <> linebreak <> y
softline :: Doc
softline = group line
softbreak :: Doc
softbreak = group linebreak
squotes :: Doc -> Doc
squotes = enclose squote squote
dquotes :: Doc -> Doc
dquotes = enclose dquote dquote
braces :: Doc -> Doc
braces = enclose lbrace rbrace
parens :: Doc -> Doc
parens = enclose lparen rparen
angles :: Doc -> Doc
angles = enclose langle rangle
brackets :: Doc -> Doc
brackets = enclose lbracket rbracket
enclose :: Doc -> Doc -> Doc -> Doc
enclose l r x = l <> x <> r
lparen :: Doc
lparen = char '('
rparen :: Doc
rparen = char ')'
langle :: Doc
langle = char '<'
rangle :: Doc
rangle = char '>'
lbrace :: Doc
lbrace = char '{'
rbrace :: Doc
rbrace = char '}'
lbracket :: Doc
lbracket = char '['
rbracket :: Doc
rbracket = char ']'
squote :: Doc
squote = char '\''
dquote :: Doc
dquote = char '"'
semi :: Doc
semi = char ';'
colon :: Doc
colon = char ':'
comma :: Doc
comma = char ','
space :: Doc
space = char ' '
dot :: Doc
dot = char '.'
backslash :: Doc
backslash = char '\\'
equals :: Doc
equals = char '='
string :: String -> Doc
string "" = empty
string ('\n':s) = line <> string s
string s = case (span (/='\n') s) of
(xs,ys) -> text xs <> string ys
bool :: Bool -> Doc
bool b = text (show b)
int :: Int -> Doc
int i = text (show i)
integer :: Integer -> Doc
integer i = text (show i)
float :: Float -> Doc
float f = text (show f)
double :: Double -> Doc
double d = text (show d)
rational :: Rational -> Doc
rational r = text (show r)
class Pretty a where
pretty :: a -> Doc
prettyList :: [a] -> Doc
prettyList = list . map pretty
instance Pretty a => Pretty [a] where
pretty = prettyList
instance Pretty Doc where
pretty = id
instance Pretty () where
pretty () = text "()"
instance Pretty Bool where
pretty b = bool b
instance Pretty Char where
pretty c = char c
prettyList s = string s
instance Pretty Int where
pretty i = int i
instance Pretty Integer where
pretty i = integer i
instance Pretty Float where
pretty f = float f
instance Pretty Double where
pretty d = double d
instance (Pretty a,Pretty b) => Pretty (a,b) where
pretty (x,y) = tupled [pretty x, pretty y]
instance (Pretty a,Pretty b,Pretty c) => Pretty (a,b,c) where
pretty (x,y,z)= tupled [pretty x, pretty y, pretty z]
instance Pretty a => Pretty (Maybe a) where
pretty Nothing = empty
pretty (Just x) = pretty x
fillBreak :: Int -> Doc -> Doc
fillBreak f x = width x (\w ->
if (w > f) then nest f linebreak
else text (spaces (f - w)))
fill :: Int -> Doc -> Doc
fill f d = width d (\w ->
if (w >= f) then empty
else text (spaces (f - w)))
width :: Doc -> (Int -> Doc) -> Doc
width d f = column (\k1 -> d <> column (\k2 -> f (k2 - k1)))
indent :: Int -> Doc -> Doc
indent i d = hang i (text (spaces i) <> d)
hang :: Int -> Doc -> Doc
hang i d = align (nest i d)
align :: Doc -> Doc
align d = column (\k ->
nesting (\i -> nest (k - i) d))
data Doc = Fail
| Empty
| Char Char
| Text !Int String
| Line
| FlatAlt Doc Doc
| Cat Doc Doc
| Nest !Int Doc
| Union Doc Doc
| Column (Int -> Doc)
| Columns (Maybe Int -> Doc)
| Nesting (Int -> Doc)
| Color ConsoleLayer ColorIntensity
Color Doc
| Intensify ConsoleIntensity Doc
| Italicize Bool Doc
| Underline Underlining Doc
| RestoreFormat (Maybe (ColorIntensity, Color))
(Maybe (ColorIntensity, Color))
(Maybe ConsoleIntensity)
(Maybe Bool)
(Maybe Underlining)
data SimpleDoc = SFail
| SEmpty
| SChar Char SimpleDoc
| SText !Int String SimpleDoc
| SLine !Int SimpleDoc
| SSGR [SGR] SimpleDoc
instance Monoid Doc where
mempty = empty
mappend = (<>)
mconcat = hcat
instance IsString Doc where
fromString = text
empty :: Doc
empty = Empty
char :: Char -> Doc
char '\n' = line
char c = Char c
text :: String -> Doc
text "" = Empty
text s = Text (length s) s
line :: Doc
line = FlatAlt Line space
linebreak :: Doc
linebreak = FlatAlt Line empty
hardline :: Doc
hardline = Line
beside :: Doc -> Doc -> Doc
beside x y = Cat x y
nest :: Int -> Doc -> Doc
nest i x = Nest i x
column, nesting :: (Int -> Doc) -> Doc
column f = Column f
nesting f = Nesting f
columns :: (Maybe Int -> Doc) -> Doc
columns f = Columns f
group :: Doc -> Doc
group x = Union (flatten x) x
flatAlt :: Doc -> Doc -> Doc
flatAlt = FlatAlt
flatten :: Doc -> Doc
flatten (FlatAlt x y) = y
flatten (Cat x y) = Cat (flatten x) (flatten y)
flatten (Nest i x) = Nest i (flatten x)
flatten Line = Fail
flatten (Union x y) = flatten x
flatten (Column f) = Column (flatten . f)
flatten (Columns f) = Columns (flatten . f)
flatten (Nesting f) = Nesting (flatten . f)
flatten (Color l i c x) = Color l i c (flatten x)
flatten (Intensify i x) = Intensify i (flatten x)
flatten (Italicize b x) = Italicize b (flatten x)
flatten (Underline u x) = Underline u (flatten x)
flatten other = other
black :: Doc -> Doc
red :: Doc -> Doc
green :: Doc -> Doc
yellow :: Doc -> Doc
blue :: Doc -> Doc
magenta :: Doc -> Doc
cyan :: Doc -> Doc
white :: Doc -> Doc
dullblack :: Doc -> Doc
dullred :: Doc -> Doc
dullgreen :: Doc -> Doc
dullyellow :: Doc -> Doc
dullblue :: Doc -> Doc
dullmagenta :: Doc -> Doc
dullcyan :: Doc -> Doc
dullwhite :: Doc -> Doc
(black, dullblack) = colorFunctions Black
(red, dullred) = colorFunctions Red
(green, dullgreen) = colorFunctions Green
(yellow, dullyellow) = colorFunctions Yellow
(blue, dullblue) = colorFunctions Blue
(magenta, dullmagenta) = colorFunctions Magenta
(cyan, dullcyan) = colorFunctions Cyan
(white, dullwhite) = colorFunctions White
color :: Color -> Doc -> Doc
dullcolor :: Color -> Doc -> Doc
color = Color Foreground Vivid
dullcolor = Color Foreground Dull
colorFunctions :: Color -> (Doc -> Doc, Doc -> Doc)
colorFunctions what = (color what, dullcolor what)
onblack :: Doc -> Doc
onred :: Doc -> Doc
ongreen :: Doc -> Doc
onyellow :: Doc -> Doc
onblue :: Doc -> Doc
onmagenta :: Doc -> Doc
oncyan :: Doc -> Doc
onwhite :: Doc -> Doc
ondullblack :: Doc -> Doc
ondullred :: Doc -> Doc
ondullgreen :: Doc -> Doc
ondullyellow :: Doc -> Doc
ondullblue :: Doc -> Doc
ondullmagenta :: Doc -> Doc
ondullcyan :: Doc -> Doc
ondullwhite :: Doc -> Doc
(onblack, ondullblack) = oncolorFunctions Black
(onred, ondullred) = oncolorFunctions Red
(ongreen, ondullgreen) = oncolorFunctions Green
(onyellow, ondullyellow) = oncolorFunctions Yellow
(onblue, ondullblue) = oncolorFunctions Blue
(onmagenta, ondullmagenta) = oncolorFunctions Magenta
(oncyan, ondullcyan) = oncolorFunctions Cyan
(onwhite, ondullwhite) = oncolorFunctions White
oncolor :: Color -> Doc -> Doc
ondullcolor :: Color -> Doc -> Doc
oncolor = Color Background Vivid
ondullcolor = Color Background Dull
oncolorFunctions :: Color -> (Doc -> Doc, Doc -> Doc)
oncolorFunctions what = (oncolor what, ondullcolor what)
bold :: Doc -> Doc
bold = Intensify BoldIntensity
debold :: Doc -> Doc
debold = Intensify NormalIntensity
underline :: Doc -> Doc
underline = Underline SingleUnderline
deunderline :: Doc -> Doc
deunderline = Underline NoUnderline
plain :: Doc -> Doc
plain Fail = Fail
plain e@Empty = e
plain c@(Char _) = c
plain t@(Text _ _) = t
plain l@Line = l
plain (FlatAlt x y) = FlatAlt (plain x) (plain y)
plain (Cat x y) = Cat (plain x) (plain y)
plain (Nest i x) = Nest i (plain x)
plain (Union x y) = Union (plain x) (plain y)
plain (Column f) = Column (plain . f)
plain (Columns f) = Columns (plain . f)
plain (Nesting f) = Nesting (plain . f)
plain (Color _ _ _ x) = plain x
plain (Intensify _ x) = plain x
plain (Italicize _ x) = plain x
plain (Underline _ x) = plain x
plain (RestoreFormat _ _ _ _ _) = Empty
data Docs = Nil
| Cons !Int Doc Docs
renderPretty :: Float -> Int -> Doc -> SimpleDoc
renderPretty = renderFits fits1
renderSmart :: Float -> Int -> Doc -> SimpleDoc
renderSmart = renderFits fitsR
renderFits :: (Int -> Int -> Int -> SimpleDoc -> Bool)
-> Float -> Int -> Doc -> SimpleDoc
renderFits fits rfrac w x
= best 0 0 Nothing Nothing Nothing Nothing Nothing (Cons 0 x Nil)
where
r = max 0 (min w (round (fromIntegral w * rfrac)))
best n k mb_fc mb_bc mb_in mb_it mb_un Nil = SEmpty
best n k mb_fc mb_bc mb_in mb_it mb_un (Cons i d ds)
= case d of
Fail -> SFail
Empty -> best_typical n k ds
Char c -> let k' = k+1 in seq k' (SChar c (best_typical n k' ds))
Text l s -> let k' = k+l in seq k' (SText l s (best_typical n k' ds))
Line -> SLine i (best_typical i i ds)
FlatAlt x _ -> best_typical n k (Cons i x ds)
Cat x y -> best_typical n k (Cons i x (Cons i y ds))
Nest j x -> let i' = i+j in seq i' (best_typical n k (Cons i' x ds))
Union x y -> nicest n k (best_typical n k (Cons i x ds))
(best_typical n k (Cons i y ds))
Column f -> best_typical n k (Cons i (f k) ds)
Columns f -> best_typical n k (Cons i (f (Just w)) ds)
Nesting f -> best_typical n k (Cons i (f i) ds)
Color l t c x -> SSGR [SetColor l t c] (best n k mb_fc' mb_bc' mb_in mb_it mb_un (Cons i x ds_restore))
where
mb_fc' = case l of { Background -> mb_fc; Foreground -> Just (t, c) }
mb_bc' = case l of { Background -> Just (t, c); Foreground -> mb_bc }
Intensify t x -> SSGR [SetConsoleIntensity t] (best n k mb_fc mb_bc (Just t) mb_it mb_un (Cons i x ds_restore))
Italicize t x -> SSGR [SetItalicized t] (best n k mb_fc mb_bc mb_in (Just t) mb_un (Cons i x ds_restore))
Underline u x -> SSGR [SetUnderlining u] (best n k mb_fc mb_bc mb_in mb_it (Just u) (Cons i x ds_restore))
RestoreFormat mb_fc' mb_bc' mb_in' mb_it' mb_un' -> SSGR sgrs (best n k mb_fc' mb_bc' mb_in' mb_it' mb_un' ds)
where
sgrs = Reset : catMaybes [
fmap (uncurry (SetColor Foreground)) mb_fc',
fmap (uncurry (SetColor Background)) mb_bc',
fmap SetConsoleIntensity mb_in',
fmap SetItalicized mb_it',
fmap SetUnderlining mb_un'
]
where
best_typical n' k' ds' = best n' k' mb_fc mb_bc mb_in mb_it mb_un ds'
ds_restore = Cons i (RestoreFormat mb_fc mb_bc mb_in mb_it mb_un) ds
nicest n k x y | fits w (min n k) width x = x
| otherwise = y
where
width = min (w - k) (r - k + n)
fits1 :: Int -> Int -> Int -> SimpleDoc -> Bool
fits1 _ _ w x | w < 0 = False
fits1 _ _ w SFail = False
fits1 _ _ w SEmpty = True
fits1 p m w (SChar c x) = fits1 p m (w - 1) x
fits1 p m w (SText l s x) = fits1 p m (w - l) x
fits1 _ _ w (SLine i x) = True
fits1 p m w (SSGR _ x) = fits1 p m w x
fitsR :: Int -> Int -> Int -> SimpleDoc -> Bool
fitsR p m w x | w < 0 = False
fitsR p m w SFail = False
fitsR p m w SEmpty = True
fitsR p m w (SChar c x) = fitsR p m (w - 1) x
fitsR p m w (SText l s x) = fitsR p m (w - l) x
fitsR p m w (SLine i x) | m < i = fitsR p m (p - i) x
| otherwise = True
fitsR p m w (SSGR _ x) = fitsR p m w x
renderCompact :: Doc -> SimpleDoc
renderCompact x
= scan 0 [x]
where
scan k [] = SEmpty
scan k (d:ds) = case d of
Fail -> SFail
Empty -> scan k ds
Char c -> let k' = k+1 in seq k' (SChar c (scan k' ds))
Text l s -> let k' = k+l in seq k' (SText l s (scan k' ds))
FlatAlt x _ -> scan k (x:ds)
Line -> SLine 0 (scan 0 ds)
Cat x y -> scan k (x:y:ds)
Nest j x -> scan k (x:ds)
Union x y -> scan k (y:ds)
Column f -> scan k (f k:ds)
Columns f -> scan k (f Nothing:ds)
Nesting f -> scan k (f 0:ds)
Color _ _ _ x -> scan k (x:ds)
Intensify _ x -> scan k (x:ds)
Italicize _ x -> scan k (x:ds)
Underline _ x -> scan k (x:ds)
RestoreFormat _ _ _ _ _ -> scan k ds
displayS :: SimpleDoc -> ShowS
displayS SFail = error $ "@SFail@ can not appear uncaught in a " ++
"rendered @SimpleDoc@"
displayS SEmpty = id
displayS (SChar c x) = showChar c . displayS x
displayS (SText l s x) = showString s . displayS x
displayS (SLine i x) = showString ('\n':indentation i) . displayS x
displayS (SSGR s x) = showString (setSGRCode s) . displayS x
displayIO :: Handle -> SimpleDoc -> IO ()
displayIO handle simpleDoc
= display simpleDoc
where
display SFail = error $ "@SFail@ can not appear uncaught in a " ++
"rendered @SimpleDoc@"
display SEmpty = return ()
display (SChar c x) = do{ hPutChar handle c; display x}
display (SText l s x) = do{ hPutStr handle s; display x}
display (SLine i x) = do{ hPutStr handle ('\n':indentation i); display x}
display (SSGR s x) = do{ hSetSGR handle s; display x}
instance Show Doc where
showsPrec d doc = displayS (renderPretty 0.4 80 doc)
putDoc :: Doc -> IO ()
putDoc doc = hPutDoc stdout doc
hPutDoc :: Handle -> Doc -> IO ()
hPutDoc handle doc = displayIO handle (renderPretty 0.4 80 doc)
spaces :: Int -> String
spaces n | n <= 0 = ""
| otherwise = replicate n ' '
indentation :: Int -> String
indentation n = spaces n