#if __GLASGOW_HASKELL__ >= 701
#endif
#ifndef TESTING
module Text.PrettyPrint.HughesPJ (
Doc, TextDetails(..),
char, text, ptext, sizedText, zeroWidthText,
int, integer, float, double, rational,
semi, comma, colon, space, equals,
lparen, rparen, lbrack, rbrack, lbrace, rbrace,
parens, brackets, braces, quotes, doubleQuotes,
empty,
(<>), (<+>), hcat, hsep,
($$), ($+$), vcat,
sep, cat,
fsep, fcat,
nest,
hang, punctuate,
isEmpty,
first, reduceDoc,
render,
Style(..),
style,
renderStyle,
Mode(..),
fullRender
) where
#endif
import Data.Monoid ( Monoid(mempty, mappend) )
import Data.String ( IsString(fromString) )
infixl 6 <>
infixl 6 <+>
infixl 5 $$, $+$
data Doc
= Empty
| NilAbove Doc
| TextBeside !TextDetails !Int Doc
| Nest !Int Doc
| Union Doc Doc
| NoDoc
| Beside Doc Bool Doc
| Above Doc Bool Doc
type RDoc = Doc
data TextDetails = Chr !Char
| Str String
| PStr String
instance Monoid Doc where
mempty = empty
mappend = (<>)
instance IsString Doc where
fromString = text
instance Show Doc where
showsPrec _ doc cont = fullRender (mode style) (lineLength style)
(ribbonsPerLine style)
txtPrinter cont doc
char :: Char -> Doc
char c = textBeside_ (Chr c) 1 Empty
text :: String -> Doc
text s = case length s of {sl -> textBeside_ (Str s) sl Empty}
ptext :: String -> Doc
ptext s = case length s of {sl -> textBeside_ (PStr s) sl Empty}
sizedText :: Int -> String -> Doc
sizedText l s = textBeside_ (Str s) l Empty
zeroWidthText :: String -> Doc
zeroWidthText = sizedText 0
empty :: Doc
empty = Empty
isEmpty :: Doc -> Bool
isEmpty Empty = True
isEmpty _ = False
indent :: Int -> String
indent !n = replicate n ' '
semi :: Doc
comma :: Doc
colon :: Doc
space :: Doc
equals :: Doc
lparen :: Doc
rparen :: Doc
lbrack :: Doc
rbrack :: Doc
lbrace :: Doc
rbrace :: Doc
semi = char ';'
comma = char ','
colon = char ':'
space = char ' '
equals = char '='
lparen = char '('
rparen = char ')'
lbrack = char '['
rbrack = char ']'
lbrace = char '{'
rbrace = char '}'
space_text, nl_text :: TextDetails
space_text = Chr ' '
nl_text = Chr '\n'
int :: Int -> Doc
integer :: Integer -> Doc
float :: Float -> Doc
double :: Double -> Doc
rational :: Rational -> Doc
int n = text (show n)
integer n = text (show n)
float n = text (show n)
double n = text (show n)
rational n = text (show n)
parens :: Doc -> Doc
brackets :: Doc -> Doc
braces :: Doc -> Doc
quotes :: Doc -> Doc
doubleQuotes :: Doc -> Doc
quotes p = char '\'' <> p <> char '\''
doubleQuotes p = char '"' <> p <> char '"'
parens p = char '(' <> p <> char ')'
brackets p = char '[' <> p <> char ']'
braces p = char '{' <> p <> char '}'
reduceDoc :: Doc -> RDoc
reduceDoc (Beside p g q) = beside p g (reduceDoc q)
reduceDoc (Above p g q) = above p g (reduceDoc q)
reduceDoc p = p
hcat :: [Doc] -> Doc
hcat = reduceAB . foldr (beside_' False) empty
hsep :: [Doc] -> Doc
hsep = reduceAB . foldr (beside_' True) empty
vcat :: [Doc] -> Doc
vcat = reduceAB . foldr (above_' False) empty
nest :: Int -> Doc -> Doc
nest k p = mkNest k (reduceDoc p)
hang :: Doc -> Int -> Doc -> Doc
hang d1 n d2 = sep [d1, nest n d2]
punctuate :: Doc -> [Doc] -> [Doc]
punctuate _ [] = []
punctuate p (x:xs) = go x xs
where go y [] = [y]
go y (z:zs) = (y <> p) : go z zs
mkNest :: Int -> Doc -> Doc
mkNest k _ | k `seq` False = undefined
mkNest k (Nest k1 p) = mkNest (k + k1) p
mkNest _ NoDoc = NoDoc
mkNest _ Empty = Empty
mkNest 0 p = p
mkNest k p = nest_ k p
mkUnion :: Doc -> Doc -> Doc
mkUnion Empty _ = Empty
mkUnion p q = p `union_` q
beside_' :: Bool -> Doc -> Doc -> Doc
beside_' _ p Empty = p
beside_' g p q = Beside p g q
above_' :: Bool -> Doc -> Doc -> Doc
above_' _ p Empty = p
above_' g p q = Above p g q
reduceAB :: Doc -> Doc
reduceAB (Above Empty _ q) = q
reduceAB (Beside Empty _ q) = q
reduceAB doc = doc
nilAbove_ :: RDoc -> RDoc
nilAbove_ p = NilAbove p
textBeside_ :: TextDetails -> Int -> RDoc -> RDoc
textBeside_ s sl p = TextBeside s sl p
nest_ :: Int -> RDoc -> RDoc
nest_ k p = Nest k p
union_ :: RDoc -> RDoc -> RDoc
union_ p q = Union p q
($$) :: Doc -> Doc -> Doc
p $$ q = above_ p False q
($+$) :: Doc -> Doc -> Doc
p $+$ q = above_ p True q
above_ :: Doc -> Bool -> Doc -> Doc
above_ p _ Empty = p
above_ Empty _ q = q
above_ p g q = Above p g q
above :: Doc -> Bool -> RDoc -> RDoc
above (Above p g1 q1) g2 q2 = above p g1 (above q1 g2 q2)
above p@(Beside _ _ _) g q = aboveNest (reduceDoc p) g 0 (reduceDoc q)
above p g q = aboveNest p g 0 (reduceDoc q)
aboveNest :: RDoc -> Bool -> Int -> RDoc -> RDoc
aboveNest _ _ k _ | k `seq` False = undefined
aboveNest NoDoc _ _ _ = NoDoc
aboveNest (p1 `Union` p2) g k q = aboveNest p1 g k q `union_`
aboveNest p2 g k q
aboveNest Empty _ k q = mkNest k q
aboveNest (Nest k1 p) g k q = nest_ k1 (aboveNest p g (k k1) q)
aboveNest (NilAbove p) g k q = nilAbove_ (aboveNest p g k q)
aboveNest (TextBeside s sl p) g k q = textBeside_ s sl rest
where
!k1 = k sl
rest = case p of
Empty -> nilAboveNest g k1 q
_ -> aboveNest p g k1 q
aboveNest (Above {}) _ _ _ = error "aboveNest Above"
aboveNest (Beside {}) _ _ _ = error "aboveNest Beside"
nilAboveNest :: Bool -> Int -> RDoc -> RDoc
nilAboveNest _ k _ | k `seq` False = undefined
nilAboveNest _ _ Empty = Empty
nilAboveNest g k (Nest k1 q) = nilAboveNest g (k + k1) q
nilAboveNest g k q | not g && k > 0
= textBeside_ (Str (indent k)) k q
| otherwise
= nilAbove_ (mkNest k q)
(<>) :: Doc -> Doc -> Doc
p <> q = beside_ p False q
(<+>) :: Doc -> Doc -> Doc
p <+> q = beside_ p True q
beside_ :: Doc -> Bool -> Doc -> Doc
beside_ p _ Empty = p
beside_ Empty _ q = q
beside_ p g q = Beside p g q
beside :: Doc -> Bool -> RDoc -> RDoc
beside NoDoc _ _ = NoDoc
beside (p1 `Union` p2) g q = beside p1 g q `union_` beside p2 g q
beside Empty _ q = q
beside (Nest k p) g q = nest_ k $! beside p g q
beside p@(Beside p1 g1 q1) g2 q2
| g1 == g2 = beside p1 g1 $! beside q1 g2 q2
| otherwise = beside (reduceDoc p) g2 q2
beside p@(Above _ _ _) g q = let !d = reduceDoc p in beside d g q
beside (NilAbove p) g q = nilAbove_ $! beside p g q
beside (TextBeside s sl p) g q = textBeside_ s sl $! rest
where
rest = case p of
Empty -> nilBeside g q
_ -> beside p g q
nilBeside :: Bool -> RDoc -> RDoc
nilBeside _ Empty = Empty
nilBeside g (Nest _ p) = nilBeside g p
nilBeside g p | g = textBeside_ space_text 1 p
| otherwise = p
sep :: [Doc] -> Doc
sep = sepX True
cat :: [Doc] -> Doc
cat = sepX False
sepX :: Bool -> [Doc] -> Doc
sepX _ [] = empty
sepX x (p:ps) = sep1 x (reduceDoc p) 0 ps
sep1 :: Bool -> RDoc -> Int -> [Doc] -> RDoc
sep1 _ _ k _ | k `seq` False = undefined
sep1 _ NoDoc _ _ = NoDoc
sep1 g (p `Union` q) k ys = sep1 g p k ys `union_`
aboveNest q False k (reduceDoc (vcat ys))
sep1 g Empty k ys = mkNest k (sepX g ys)
sep1 g (Nest n p) k ys = nest_ n (sep1 g p (k n) ys)
sep1 _ (NilAbove p) k ys = nilAbove_
(aboveNest p False k (reduceDoc (vcat ys)))
sep1 g (TextBeside s sl p) k ys = textBeside_ s sl (sepNB g p (k sl) ys)
sep1 _ (Above {}) _ _ = error "sep1 Above"
sep1 _ (Beside {}) _ _ = error "sep1 Beside"
sepNB :: Bool -> Doc -> Int -> [Doc] -> Doc
sepNB g (Nest _ p) k ys
= sepNB g p k ys
sepNB g Empty k ys
= oneLiner (nilBeside g (reduceDoc rest)) `mkUnion`
nilAboveNest False k (reduceDoc (vcat ys))
where
rest | g = hsep ys
| otherwise = hcat ys
sepNB g p k ys
= sep1 g p k ys
fcat :: [Doc] -> Doc
fcat = fill False
fsep :: [Doc] -> Doc
fsep = fill True
fill :: Bool -> [Doc] -> RDoc
fill _ [] = empty
fill g (p:ps) = fill1 g (reduceDoc p) 0 ps
fill1 :: Bool -> RDoc -> Int -> [Doc] -> Doc
fill1 _ _ k _ | k `seq` False = undefined
fill1 _ NoDoc _ _ = NoDoc
fill1 g (p `Union` q) k ys = fill1 g p k ys `union_`
aboveNest q False k (fill g ys)
fill1 g Empty k ys = mkNest k (fill g ys)
fill1 g (Nest n p) k ys = nest_ n (fill1 g p (k n) ys)
fill1 g (NilAbove p) k ys = nilAbove_ (aboveNest p False k (fill g ys))
fill1 g (TextBeside s sl p) k ys = textBeside_ s sl (fillNB g p (k sl) ys)
fill1 _ (Above {}) _ _ = error "fill1 Above"
fill1 _ (Beside {}) _ _ = error "fill1 Beside"
fillNB :: Bool -> Doc -> Int -> [Doc] -> Doc
fillNB _ _ k _ | k `seq` False = undefined
fillNB g (Nest _ p) k ys = fillNB g p k ys
fillNB _ Empty _ [] = Empty
fillNB g Empty k (Empty:ys) = fillNB g Empty k ys
fillNB g Empty k (y:ys) = fillNBE g k y ys
fillNB g p k ys = fill1 g p k ys
fillNBE :: Bool -> Int -> Doc -> [Doc] -> Doc
fillNBE g k y ys
= nilBeside g (fill1 g ((elideNest . oneLiner . reduceDoc) y) k' ys)
`mkUnion` nilAboveNest False k (fill g (y:ys))
where k' = if g then k 1 else k
elideNest :: Doc -> Doc
elideNest (Nest _ d) = d
elideNest d = d
best :: Int
-> Int
-> RDoc
-> RDoc
best w0 r p0
= get w0 p0
where
get w _ | w == 0 && False = undefined
get _ Empty = Empty
get _ NoDoc = NoDoc
get w (NilAbove p) = nilAbove_ (get w p)
get w (TextBeside s sl p) = textBeside_ s sl (get1 w sl p)
get w (Nest k p) = nest_ k (get (w k) p)
get w (p `Union` q) = nicest w r (get w p) (get w q)
get _ (Above {}) = error "best get Above"
get _ (Beside {}) = error "best get Beside"
get1 w _ _ | w == 0 && False = undefined
get1 _ _ Empty = Empty
get1 _ _ NoDoc = NoDoc
get1 w sl (NilAbove p) = nilAbove_ (get (w sl) p)
get1 w sl (TextBeside t tl p) = textBeside_ t tl (get1 w (sl + tl) p)
get1 w sl (Nest _ p) = get1 w sl p
get1 w sl (p `Union` q) = nicest1 w r sl (get1 w sl p)
(get1 w sl q)
get1 _ _ (Above {}) = error "best get1 Above"
get1 _ _ (Beside {}) = error "best get1 Beside"
nicest :: Int -> Int -> Doc -> Doc -> Doc
nicest !w !r p q = nicest1 w r 0 p q
nicest1 :: Int -> Int -> Int -> Doc -> Doc -> Doc
nicest1 !w !r !sl p q | fits ((w `min` r) sl) p = p
| otherwise = q
fits :: Int
-> Doc
-> Bool
fits n _ | n < 0 = False
fits _ NoDoc = False
fits _ Empty = True
fits _ (NilAbove _) = True
fits n (TextBeside _ sl p) = fits (n sl) p
fits _ (Above {}) = error "fits Above"
fits _ (Beside {}) = error "fits Beside"
fits _ (Union {}) = error "fits Union"
fits _ (Nest {}) = error "fits Nest"
first :: Doc -> Doc -> Doc
first p q | nonEmptySet p = p
| otherwise = q
nonEmptySet :: Doc -> Bool
nonEmptySet NoDoc = False
nonEmptySet (_ `Union` _) = True
nonEmptySet Empty = True
nonEmptySet (NilAbove _) = True
nonEmptySet (TextBeside _ _ p) = nonEmptySet p
nonEmptySet (Nest _ p) = nonEmptySet p
nonEmptySet (Above {}) = error "nonEmptySet Above"
nonEmptySet (Beside {}) = error "nonEmptySet Beside"
oneLiner :: Doc -> Doc
oneLiner NoDoc = NoDoc
oneLiner Empty = Empty
oneLiner (NilAbove _) = NoDoc
oneLiner (TextBeside s sl p) = textBeside_ s sl (oneLiner p)
oneLiner (Nest k p) = nest_ k (oneLiner p)
oneLiner (p `Union` _) = oneLiner p
oneLiner (Above {}) = error "oneLiner Above"
oneLiner (Beside {}) = error "oneLiner Beside"
data Style
= Style { mode :: Mode
, lineLength :: Int
, ribbonsPerLine :: Float
}
style :: Style
style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode }
data Mode = PageMode
| ZigZagMode
| LeftMode
| OneLineMode
render :: Doc -> String
render doc = fullRender (mode style) (lineLength style) (ribbonsPerLine style)
txtPrinter "" doc
renderStyle :: Style -> Doc -> String
renderStyle s doc = fullRender (mode s) (lineLength s) (ribbonsPerLine s)
txtPrinter "" doc
txtPrinter :: TextDetails -> String -> String
txtPrinter (Chr c) s = c:s
txtPrinter (Str s1) s2 = s1 ++ s2
txtPrinter (PStr s1) s2 = s1 ++ s2
fullRender :: Mode
-> Int
-> Float
-> (TextDetails -> a -> a)
-> a
-> Doc
-> a
fullRender OneLineMode _ _ txt end doc
= easy_display space_text (\_ y -> y) txt end (reduceDoc doc)
fullRender LeftMode _ _ txt end doc
= easy_display nl_text first txt end (reduceDoc doc)
fullRender m lineLen ribbons txt rest doc
= display m lineLen ribbonLen txt rest doc'
where
doc' = best bestLineLen ribbonLen (reduceDoc doc)
bestLineLen, ribbonLen :: Int
ribbonLen = round (fromIntegral lineLen / ribbons)
bestLineLen = case m of
ZigZagMode -> maxBound
_ -> lineLen
easy_display :: TextDetails
-> (Doc -> Doc -> Doc)
-> (TextDetails -> a -> a)
-> a
-> Doc
-> a
easy_display nl_space_text choose txt end doc
= lay doc
where
lay NoDoc = error "easy_display: NoDoc"
lay (Union p q) = lay (choose p q)
lay (Nest _ p) = lay p
lay Empty = end
lay (NilAbove p) = nl_space_text `txt` lay p
lay (TextBeside s _ p) = s `txt` lay p
lay (Above {}) = error "easy_display Above"
lay (Beside {}) = error "easy_display Beside"
display :: Mode -> Int -> Int -> (TextDetails -> a -> a) -> a -> Doc -> a
display m !page_width !ribbon_width txt end doc
= case page_width ribbon_width of { gap_width ->
case gap_width `quot` 2 of { shift ->
let
lay k _ | k `seq` False = undefined
lay k (Nest k1 p) = lay (k + k1) p
lay _ Empty = end
lay k (NilAbove p) = nl_text `txt` lay k p
lay k (TextBeside s sl p)
= case m of
ZigZagMode | k >= gap_width
-> nl_text `txt` (
Str (replicate shift '/') `txt` (
nl_text `txt`
lay1 (k shift) s sl p ))
| k < 0
-> nl_text `txt` (
Str (replicate shift '\\') `txt` (
nl_text `txt`
lay1 (k + shift) s sl p ))
_ -> lay1 k s sl p
lay _ (Above {}) = error "display lay Above"
lay _ (Beside {}) = error "display lay Beside"
lay _ NoDoc = error "display lay NoDoc"
lay _ (Union {}) = error "display lay Union"
lay1 !k s !sl p = let !r = k + sl
in Str (indent k) `txt` (s `txt` lay2 r p)
lay2 k _ | k `seq` False = undefined
lay2 k (NilAbove p) = nl_text `txt` lay k p
lay2 k (TextBeside s sl p) = s `txt` lay2 (k + sl) p
lay2 k (Nest _ p) = lay2 k p
lay2 _ Empty = end
lay2 _ (Above {}) = error "display lay2 Above"
lay2 _ (Beside {}) = error "display lay2 Beside"
lay2 _ NoDoc = error "display lay2 NoDoc"
lay2 _ (Union {}) = error "display lay2 Union"
in
lay 0 doc
}}