{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
module Text.PrettyPrint.Mainland (
Doc,
text, bool, char, string, int, integer, float, double, rational,
strictText, lazyText,
star, colon, comma, dot, equals, semi, space, spaces,
backquote, squote, dquote,
langle, rangle, lbrace, rbrace, lbracket, rbracket, lparen, rparen,
empty,
srcloc, line, softline, softbreak,
(<|>), (<+>), (</>), (<+/>), (<//>),
group, flatten,
enclose, squotes, dquotes, angles, backquotes, braces, brackets, parens,
parensIf,
folddoc, spread, stack, cat, sep,
punctuate, commasep, semisep,
enclosesep, tuple, list,
align, hang, indent,
nest, column, nesting,
width, fill, fillbreak,
faildoc, errordoc,
RDoc(..),
render, renderCompact,
displayS, prettyS, pretty, prettyCompactS, prettyCompact,
displayPragmaS, prettyPragmaS, prettyPragma,
displayLazyText, prettyLazyText,
displayPragmaLazyText, prettyPragmaLazyText,
putDoc, putDocLn, hPutDoc, hPutDocLn
) where
import Data.Loc (L(..),
Loc(..),
Located(..),
Pos(..),
posFile,
posLine)
import qualified Data.Map as Map
#if !(MIN_VERSION_base(4,9,0))
import Data.Monoid (Monoid(..), (<>))
#endif /* !(MIN_VERSION_base(4,9,0)) */
#if MIN_VERSION_base(4,9,0) && !(MIN_VERSION_base(4,11,0))
import Data.Semigroup (Semigroup(..))
#endif
import qualified Data.Set as Set
import Data.String (IsString(..))
import qualified Data.Text as T
import qualified Data.Text.Lazy.IO as TIO
import qualified Data.Text.Lazy as L
import qualified Data.Text.Lazy.Builder as B
import System.IO (Handle)
data Doc
= Empty
| Char {-# UNPACK #-} !Char
| String {-# UNPACK #-} !Int String
| Text T.Text
| LazyText L.Text
| Line
| Nest {-# UNPACK #-} !Int Doc
| SrcLoc Loc
| Doc `Cat` Doc
| Doc `Alt` Doc
| Column (Int -> Doc)
| Nesting (Int -> Doc)
#if MIN_VERSION_base(4,9,0)
instance Semigroup Doc where
(<>) = Cat
#endif
instance Monoid Doc where
mempty = empty
#if !(MIN_VERSION_base(4,11,0))
mappend = Cat
#endif
instance IsString Doc where
fromString s = string s
text :: String -> Doc
text s = String (length s) s
bool :: Bool -> Doc
bool b = text (show b)
char :: Char -> Doc
char '\n' = line
char c = Char c
string :: String -> Doc
string "" = empty
string ('\n' : s) = line <> string s
string s = case span (/= '\n') s of
(xs, ys) -> text xs <> string ys
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)
strictText :: T.Text -> Doc
strictText = Text
lazyText :: L.Text -> Doc
lazyText = LazyText
star :: Doc
star = char '*'
colon :: Doc
colon = char ':'
comma :: Doc
comma = char ','
dot :: Doc
dot = char '.'
equals :: Doc
equals = char '='
semi :: Doc
semi = char ';'
space :: Doc
space = char ' '
spaces :: Int -> Doc
spaces n = text (replicate n ' ')
backquote :: Doc
backquote = char '`'
squote :: Doc
squote = char '\''
dquote :: Doc
dquote = 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 ']'
lparen :: Doc
lparen = char '('
rparen :: Doc
rparen = char ')'
empty :: Doc
empty = Empty
srcloc :: Located a => a -> Doc
srcloc x = SrcLoc (locOf x)
line :: Doc
line = Line
softline :: Doc
softline = space `Alt` line
softbreak :: Doc
softbreak = empty `Alt` line
#if !MIN_VERSION_base(4,5,0)
infixr 6 <>
#endif /* !MIN_VERSION_base(4,5,0) */
infixr 6 <+>
infixr 5 </>, <+/>, <//>
infixl 3 <|>
#if !MIN_VERSION_base(4,5,0)
(<>) :: Doc -> Doc -> Doc
x <> y = x `Cat` y
#endif /* !MIN_VERSION_base(4,5,0) */
(<+>) :: Doc -> Doc -> Doc
Empty <+> y = y
x <+> Empty = x
x <+> y = x <> space <> y
(</>) :: Doc -> Doc -> Doc
Empty </> y = y
x </> Empty = x
x </> y = x <> line <> y
(<+/>) :: Doc -> Doc -> Doc
Empty <+/> y = y
x <+/> Empty = x
x <+/> y = x <> softline <> y
(<//>) :: Doc -> Doc -> Doc
x <//> y = x <> softbreak <> y
(<|>) :: Doc -> Doc -> Doc
x <|> y = x `Alt` y
group :: Doc -> Doc
group d = flatten d `Alt` d
flatten :: Doc -> Doc
flatten Empty = Empty
flatten (Char c) = Char c
flatten (String l s) = String l s
flatten (Text s) = Text s
flatten (LazyText s) = LazyText s
flatten Line = Char ' '
flatten (x `Cat` y) = flatten x `Cat` flatten y
flatten (Nest i x) = Nest i (flatten x)
flatten (x `Alt` _) = flatten x
flatten (SrcLoc loc) = SrcLoc loc
flatten (Column f) = Column (flatten . f)
flatten (Nesting f) = Nesting (flatten . f)
enclose :: Doc -> Doc -> Doc -> Doc
enclose left right d = left <> d <> right
squotes :: Doc -> Doc
squotes = enclose squote squote . align
dquotes :: Doc -> Doc
dquotes = enclose dquote dquote . align
angles :: Doc -> Doc
angles = enclose langle rangle . align
backquotes :: Doc -> Doc
backquotes = enclose backquote backquote . align
braces :: Doc -> Doc
braces = enclose lbrace rbrace . align
brackets :: Doc -> Doc
brackets = enclose lbracket rbracket . align
parens :: Doc -> Doc
parens = enclose lparen rparen . align
parensIf :: Bool -> Doc -> Doc
parensIf True doc = parens doc
parensIf False doc = doc
folddoc :: (Doc -> Doc -> Doc) -> [Doc] -> Doc
folddoc _ [] = empty
folddoc _ [x] = x
folddoc f (x:xs) = f x (folddoc f xs)
spread :: [Doc] -> Doc
spread = folddoc (<+>)
stack :: [Doc] -> Doc
stack = folddoc (</>)
cat :: [Doc] -> Doc
cat = group . folddoc (<//>)
sep :: [Doc] -> Doc
sep = group . folddoc (<+/>)
punctuate :: Doc -> [Doc] -> [Doc]
punctuate _ [] = []
punctuate _ [d] = [d]
punctuate p (d:ds) = (d <> p) : punctuate p ds
commasep :: [Doc] -> Doc
commasep = align . sep . punctuate comma
semisep :: [Doc] -> Doc
semisep = align . sep . punctuate semi
enclosesep :: Doc -> Doc -> Doc -> [Doc] -> Doc
enclosesep left right p ds =
case ds of
[] -> left <> right
[d] -> left <> d <> right
_ -> left <> align (sep (punctuate p ds)) <> right
tuple :: [Doc] -> Doc
tuple = enclosesep lparen rparen comma
list :: [Doc] -> Doc
list = enclosesep lbracket rbracket comma
align :: Doc -> Doc
align d = column $ \k ->
nesting $ \i ->
nest (k - i) d
hang :: Int -> Doc -> Doc
hang i d = align (nest i d)
indent :: Int -> Doc -> Doc
indent i d = align (nest i (spaces i <> d))
nest :: Int -> Doc -> Doc
nest i d = Nest i d
column :: (Int -> Doc) -> Doc
column = Column
nesting :: (Int -> Doc) -> Doc
nesting = Nesting
width :: Doc -> (Int -> Doc) -> Doc
width d f = column $ \k1 -> d <> (column $ \k2 -> f (k2 - k1))
fill :: Int -> Doc -> Doc
fill f d = width d $ \w ->
if w >= f
then empty
else spaces (f - w)
fillbreak :: Int -> Doc -> Doc
fillbreak f d = width d $ \w ->
if (w > f)
then nest f line
else spaces (f - w)
#if MIN_VERSION_base(4,13,0)
faildoc :: MonadFail m => Doc -> m a
#else
faildoc :: Monad m => Doc -> m a
#endif
faildoc = fail . pretty 80
errordoc :: Doc -> a
errordoc = error . pretty 80
data RDoc
= REmpty
| RChar {-# UNPACK #-} !Char RDoc
| RString {-# UNPACK #-} !Int String RDoc
| RText T.Text RDoc
| RLazyText L.Text RDoc
| RPos Pos RDoc
| RLine {-# UNPACK #-} !Int RDoc
render :: Int -> Doc -> RDoc
render w x = best w 0 x
type RDocS = RDoc -> RDoc
data Docs
= Nil
| Cons {-# UNPACK #-} !Int Doc Docs
best :: Int -> Int -> Doc -> RDoc
best !w k x = be True Nothing Nothing k id (Cons 0 x Nil)
where
be :: Bool
-> Maybe Pos
-> Maybe Pos
-> Int
-> RDocS
-> Docs
-> RDoc
be _ _ _ !_ f Nil = f REmpty
be nl p p' !k f (Cons i d ds) =
case d of
Empty -> be nl p p' k f ds
Char c -> be False p p' (k+1) (f . prag . RChar c) ds
String l s -> be False p p' (k+l) (f . prag . RString l s) ds
Text s -> be False p p' (k+T.length s) (f . prag . RText s) ds
LazyText s -> be False p p' (k+fromIntegral (L.length s)) (f . prag . RLazyText s) ds
Line -> (f . RLine i) (be True p'' Nothing i id ds)
x `Cat` y -> be nl p p' k f (Cons i x (Cons i y ds))
Nest j x -> be nl p p' k f (Cons (i+j) x ds)
x `Alt` y -> better k f (be nl p p' k id (Cons i x ds))
(be nl p p' k id (Cons i y ds))
SrcLoc loc -> be nl p (updatePos p' loc) k f ds
Column g -> be nl p p' k f (Cons i (g k) ds)
Nesting g -> be nl p p' k f (Cons i (g i) ds)
where
p'' :: Maybe Pos
prag :: RDocS
(p'', prag) = lineLoc p p'
lineLoc :: Maybe Pos
-> Maybe Pos
-> (Maybe Pos, RDocS)
lineLoc Nothing Nothing = (Nothing, noPragma)
lineLoc Nothing (Just p) = (Just p, pragma p)
lineLoc (Just p1) (Just p2)
| posFile p2 == posFile p1 &&
posLine p2 == posLine p1 + 1 = (Just p2, noPragma)
| otherwise = (Just p2, pragma p2)
lineLoc (Just p1) Nothing = (Just (advance p1), noPragma)
where
advance :: Pos -> Pos
advance (Pos f l c coff) = Pos f (l+1) c coff
noPragma :: RDocS
noPragma = id
pragma :: Pos -> RDocS
pragma p | nl = RPos p
| otherwise = id
better :: Int -> RDocS -> RDoc -> RDoc -> RDoc
better !k f x y | fits (w - k) x = f x
| otherwise = f y
fits :: Int -> RDoc -> Bool
fits !w _ | w < 0 = False
fits !_ REmpty = True
fits !w (RChar _ x) = fits (w - 1) x
fits !w (RString l _ x) = fits (w - l) x
fits !w (RText s x) = fits (w - T.length s) x
fits !w (RLazyText s x) = fits (w - fromIntegral (L.length s)) x
fits !w (RPos _ x) = fits w x
fits !_ (RLine _ _) = True
updatePos :: Maybe Pos -> Loc -> Maybe Pos
updatePos Nothing NoLoc = Nothing
updatePos _ (Loc p _) = Just p
updatePos (Just p) NoLoc = Just p
renderCompact :: Doc -> RDoc
renderCompact doc = scan 0 [doc]
where
scan :: Int -> [Doc] -> RDoc
scan !_ [] = REmpty
scan !k (d:ds) =
case d of
Empty -> scan k ds
Char c -> RChar c (scan (k+1) ds)
String l s -> RString l s (scan (k+l) ds)
Text s -> RText s (scan (k+T.length s) ds)
LazyText s -> RLazyText s (scan (k+fromIntegral (L.length s)) ds)
Line -> RLine 0 (scan 0 ds)
Nest _ x -> scan k (x:ds)
SrcLoc _ -> scan k ds
Cat x y -> scan k (x:y:ds)
Alt x _ -> scan k (x:ds)
Column f -> scan k (f k:ds)
Nesting f -> scan k (f 0:ds)
displayS :: RDoc -> ShowS
displayS = go
where
go :: RDoc -> ShowS
go REmpty = id
go (RChar c x) = showChar c . go x
go (RString _ s x) = showString s . go x
go (RText s x) = showString (T.unpack s) . go x
go (RLazyText s x) = showString (L.unpack s) . go x
go (RPos _ x) = go x
go (RLine i x) = showString ('\n' : replicate i ' ') . go x
prettyS :: Int -> Doc -> ShowS
prettyS w x = displayS (render w x)
pretty :: Int -> Doc -> String
pretty w x = prettyS w x ""
prettyCompactS :: Doc -> ShowS
prettyCompactS x = displayS (renderCompact x)
prettyCompact :: Doc -> String
prettyCompact x = prettyCompactS x ""
displayPragmaS :: RDoc -> ShowS
displayPragmaS = go
where
go :: RDoc -> ShowS
go REmpty = id
go (RChar c x) = showChar c . go x
go (RString _ s x) = showString s . go x
go (RText s x) = showString (T.unpack s) . go x
go (RLazyText s x) = showString (L.unpack s) . go x
go (RPos p x) = showPos p .
showChar '\n' .
go x
go (RLine i x) = case x of
RPos p x' -> showChar '\n' .
showPos p .
showString ('\n' : replicate i ' ') .
go x'
_ -> showString ('\n' : replicate i ' ') .
go x
showPos :: Pos -> ShowS
showPos p =
showString "#line " .
shows (posLine p) .
showChar ' ' .
showChar '"' .
showString (posFile p) .
showChar '"'
prettyPragmaS :: Int -> Doc -> ShowS
prettyPragmaS w x = displayPragmaS (render w x)
prettyPragma :: Int -> Doc -> String
prettyPragma w x = prettyPragmaS w x ""
displayLazyText :: RDoc -> L.Text
displayLazyText = B.toLazyText . go
where
go :: RDoc -> B.Builder
go REmpty = mempty
go (RChar c x) = B.singleton c `mappend` go x
go (RString _ s x) = B.fromString s `mappend` go x
go (RText s x) = B.fromText s `mappend` go x
go (RLazyText s x) = B.fromLazyText s `mappend` go x
go (RPos _ x) = go x
go (RLine i x) = B.fromString ('\n':replicate i ' ') `mappend` go x
prettyLazyText :: Int -> Doc -> L.Text
prettyLazyText w x = displayLazyText (render w x)
displayPragmaLazyText :: RDoc -> L.Text
displayPragmaLazyText = B.toLazyText . go
where
go :: RDoc -> B.Builder
go REmpty = mempty
go (RChar c x) = B.singleton c `mappend` go x
go (RText s x) = B.fromText s `mappend` go x
go (RLazyText s x) = B.fromLazyText s `mappend` go x
go (RString _ s x) = B.fromString s `mappend` go x
go (RPos p x) = displayPos p `mappend`
B.singleton '\n' `mappend`
go x
go (RLine i x) = case x of
RPos p x' -> B.singleton '\n' `mappend`
displayPos p `mappend`
B.fromString ('\n':replicate i ' ') `mappend`
go x'
_ -> B.fromString ('\n':replicate i ' ') `mappend`
go x
displayPos :: Pos -> B.Builder
displayPos p =
B.fromString "#line " `mappend`
renderPosLine p `mappend`
B.singleton ' ' `mappend`
renderPosFile p
renderPosLine :: Pos -> B.Builder
renderPosLine = go . renderCompact . int . posLine
renderPosFile :: Pos -> B.Builder
renderPosFile = go . renderCompact . enclose dquote dquote . string . posFile
prettyPragmaLazyText :: Int -> Doc -> L.Text
prettyPragmaLazyText w x = displayPragmaLazyText (render w x)
putDoc :: Doc -> IO ()
putDoc = TIO.putStr . prettyLazyText 80
putDocLn :: Doc -> IO ()
putDocLn = TIO.putStrLn . prettyLazyText 80
hPutDoc :: Handle -> Doc -> IO ()
hPutDoc h = TIO.hPutStr h . prettyLazyText 80
hPutDocLn :: Handle -> Doc -> IO ()
hPutDocLn h = TIO.hPutStrLn h . prettyLazyText 80