module Text.LaTeX.Base.Pretty (
prettyLaTeX
, docLaTeX
) where
import Text.LaTeX.Base.Syntax
import Text.LaTeX.Base.Render
import Text.PrettyPrint.Free
( Doc, text, char
, backslash, line, hardline
, braces, brackets
, indent, align, vsep
, list, encloseSep
, renderSmart, displayS
)
import Data.Text (unpack,lines)
import Data.Monoid (mconcat,mempty)
docLaTeX :: LaTeX -> Doc ()
docLaTeX (TeXRaw t) = text $ unpack t
docLaTeX (TeXComm n as) = backslash <> text n <> align (mconcat (fmap docTeXArg as)) <> line
docLaTeX (TeXCommS n) = backslash <> text n <> line
docLaTeX (TeXEnv n as b) =
let a = FixArg $ fromString n
in mconcat
[ line
, docLaTeX $ TeXComm "begin" $ a : as
, indent 4 $ docLaTeX b
, line
, docLaTeX $ TeXComm "end" [a]
]
docLaTeX (TeXMath t b) =
let (l,r) =
case t of
Parentheses -> ("\\(","\\)")
Square -> ("\\[","\\]")
Dollar -> ("$","$")
in text l <> docLaTeX b <> text r
docLaTeX (TeXLineBreak m b) =
text "\\\\" <> maybe mempty (brackets . text . unpack . render) m <> ( if b then text "*" else mempty )
docLaTeX (TeXBraces b) = braces $ docLaTeX b
docLaTeX (TeXComment t) =
let ls = Data.Text.lines t
in if null ls
then char '%' <> hardline
else (align $ vsep $ fmap (text . ("% "++) . unpack) ls) <> hardline
docLaTeX (TeXSeq l1 l2) = docLaTeX l1 <> docLaTeX l2
docLaTeX TeXEmpty = mempty
docTeXArg :: TeXArg -> Doc ()
docTeXArg (FixArg l) = braces $ docLaTeX l
docTeXArg (OptArg l) = brackets $ docLaTeX l
docTeXArg (MOptArg ls) =
if null ls then mempty
else list $ fmap docLaTeX ls
docTeXArg (SymArg l) = docTeXArg $ MSymArg [l]
docTeXArg (MSymArg ls) = encloseSep (char '<') (char '>') (char ',') $ fmap docLaTeX ls
prettyLaTeX :: LaTeX -> String
prettyLaTeX l = displayS (renderSmart 60 (docLaTeX l)) []