{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
module Render.Latex(latexFromColSpans, latexInline, latexPackages, subAndSuperscripts) where
import Data.Text(Text)
import qualified Data.Text as T
import Data.Char(isAlpha, isAsciiLower, isAsciiUpper, isDigit)
import Text.LaTeX.Base.Syntax(protectText)
import Data.Maybe (fromMaybe)
import Alignment ( Align(..) )
import Render.Common(TokensWithColSpan)
import Token(MyTok(..))
import Util(unbrace)
protectTextMath :: Text -> Text
protectTextMath :: Text -> Text
protectTextMath = Text -> Text
processText
where
processText :: Text -> Text
processText :: Text -> Text
processText Text
t
| Text -> Bool
T.null Text
t = Text
""
| Text
"\\\\" Text -> Text -> Bool
`T.isPrefixOf` Text
t = Text
"\\setminus " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
processText (Int -> Text -> Text
T.drop Int
2 Text
t)
| Text
"\\/" Text -> Text -> Bool
`T.isPrefixOf` Text
t = Text
"\\land " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
processText (Int -> Text -> Text
T.drop Int
2 Text
t)
| Text
"/\\" Text -> Text -> Bool
`T.isPrefixOf` Text
t = Text
"\\lor " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
processText (Int -> Text -> Text
T.drop Int
2 Text
t)
| Just (Char
'\\', Text
rest) <- Text -> Maybe (Char, Text)
T.uncons Text
t
, Just (Char
nextChar, Text
_) <- Text -> Maybe (Char, Text)
T.uncons Text
rest
, Char -> Bool
isAlphaNum Char
nextChar = Text
"\\lambda " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
processText Text
rest
| Just (Char
'\\', Text
rest) <- Text -> Maybe (Char, Text)
T.uncons Text
t = Text
"\\backslash " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
processText Text
rest
| Bool
otherwise =
let (Char
c, Text
rest) = (Char, Text) -> Maybe (Char, Text) -> (Char, Text)
forall a. a -> Maybe a -> a
fromMaybe (Char
' ', Text
"") (Maybe (Char, Text) -> (Char, Text))
-> Maybe (Char, Text) -> (Char, Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe (Char, Text)
T.uncons Text
t
in Char -> Text
escapeChar Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
processText Text
rest
escapeChar :: Char -> Text
escapeChar :: Char -> Text
escapeChar Char
'#' = Text
"\\#"
escapeChar Char
'$' = Text
"\\$"
escapeChar Char
'%' = Text
"\\%"
escapeChar Char
'&' = Text
"\\&"
escapeChar Char
'_' = Text
"\\_"
escapeChar Char
'{' = Text
"\\{"
escapeChar Char
'}' = Text
"\\}"
escapeChar Char
c = Char -> Text
T.singleton Char
c
isAlphaNum :: Char -> Bool
isAlphaNum :: Char -> Bool
isAlphaNum Char
c = Char -> Bool
isAsciiLower Char
c Bool -> Bool -> Bool
|| Char -> Bool
isAsciiUpper Char
c Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
c
latexFromColSpans :: Int -> [[TokensWithColSpan]] -> Text
latexFromColSpans :: Int -> [[TokensWithColSpan]] -> Text
latexFromColSpans Int
cols =
Int -> Text -> Text
wrapTable Int
cols
(Text -> Text)
-> ([[TokensWithColSpan]] -> Text) -> [[TokensWithColSpan]] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines
([Text] -> Text)
-> ([[TokensWithColSpan]] -> [Text])
-> [[TokensWithColSpan]]
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([TokensWithColSpan] -> Text) -> [[TokensWithColSpan]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ( (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\\\\")
(Text -> Text)
-> ([TokensWithColSpan] -> Text) -> [TokensWithColSpan] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
" & "
([Text] -> Text)
-> ([TokensWithColSpan] -> [Text]) -> [TokensWithColSpan] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TokensWithColSpan -> Text) -> [TokensWithColSpan] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TokensWithColSpan -> Text
renderColSpan )
renderColSpan :: TokensWithColSpan -> Text
renderColSpan :: TokensWithColSpan -> Text
renderColSpan ([(MyTok
TBlank, Text
txt)], Int
colSpan, Align
AIndent) =
[Text] -> Text
T.concat [ Text
"\\multicolumn{", String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
colSpan
, Text
"}{p{", String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
txt
, Text
"ex}}{", Text -> Text
protectText Text
txt
, Text
"\\,}" ]
renderColSpan ([(MyTok, Text)]
toks, Int
colSpan, Align
alignment) =
[Text] -> Text
T.concat [ Text
"\\multicolumn{", String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
colSpan
, Text
"}{", Align -> Text
forall {a}. IsString a => Align -> a
alignMark Align
alignment
, Text
"}{$", [(MyTok, Text)] -> Text
latexInline [(MyTok, Text)]
toks
, Text
"$}" ]
where
alignMark :: Align -> a
alignMark Align
ACenter = a
"c"
alignMark Align
ALeft = a
"l"
alignMark Align
AIndent = a
"l"
wrapTable :: Int -> Text -> Text
wrapTable :: Int -> Text -> Text
wrapTable Int
cols Text
txt =
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [
Text
"\\setlength{\\tabcolsep}{1pt}\n"
, Text
"\\begin{tabular}{"
, Int -> Text -> Text
T.replicate (Int
colsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Text
"l"
, Text
"}\n"
, Text
txt, Text
"\n\\end{tabular}"
]
preformatTokens :: [(MyTok, b)] -> [(MyTok, b)]
preformatTokens [] = []
preformatTokens ((MyTok
TOther, b
"`"):(MyTok
TVar, b
"elem"):(MyTok
TOther, b
"`"):[(MyTok, b)]
rest) = (MyTok
TOperator, b
"elem")(MyTok, b) -> [(MyTok, b)] -> [(MyTok, b)]
forall a. a -> [a] -> [a]
:[(MyTok, b)] -> [(MyTok, b)]
preformatTokens [(MyTok, b)]
rest
preformatTokens ((MyTok, b)
a :[(MyTok, b)]
rest) = (MyTok, b)
a (MyTok, b) -> [(MyTok, b)] -> [(MyTok, b)]
forall a. a -> [a] -> [a]
:[(MyTok, b)] -> [(MyTok, b)]
preformatTokens [(MyTok, b)]
rest
latexInline :: [(MyTok, Text)] -> Text
latexInline :: [(MyTok, Text)] -> Text
latexInline = [Text] -> Text
T.concat
([Text] -> Text)
-> ([(MyTok, Text)] -> [Text]) -> [(MyTok, Text)] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((MyTok, Text) -> Text) -> [(MyTok, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (MyTok, Text) -> Text
formatToken
([(MyTok, Text)] -> [Text])
-> ([(MyTok, Text)] -> [(MyTok, Text)])
-> [(MyTok, Text)]
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(MyTok, Text)] -> [(MyTok, Text)]
forall {b}. (Eq b, IsString b) => [(MyTok, b)] -> [(MyTok, b)]
preformatTokens
subAndSuperscripts :: Text -> Text
subAndSuperscripts :: Text -> Text
subAndSuperscripts Text
"" = Text
" "
subAndSuperscripts Text
"_" = Text
"\\_"
subAndSuperscripts Text
t = case HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"_" Text
t of
[] -> Text
""
(Text
x:[Text]
xs) -> Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
processSegments [Text]
xs
where
processSegments :: [Text] -> Text
processSegments :: [Text] -> Text
processSegments [] = Text
""
processSegments (Text
"":[Text]
rest) = case [Text]
rest of
[] -> Text
""
[Text]
_ -> let remainingText :: Text
remainingText = Text -> [Text] -> Text
T.intercalate Text
"_" [Text]
rest
in Text
"\\textsuperscript{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
subAndSuperscripts Text
remainingText Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
processSegments (Text
x:[Text]
xs) = Text
"\\textsubscript{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
processSegments [Text]
xs
pattern OpOrOther :: Text -> (MyTok, Text)
pattern $mOpOrOther :: forall {r}. (MyTok, Text) -> (Text -> r) -> ((# #) -> r) -> r
OpOrOther txt <- (matchOpOrOther -> Just txt)
matchOpOrOther :: (MyTok, Text) -> Maybe Text
matchOpOrOther :: (MyTok, Text) -> Maybe Text
matchOpOrOther (MyTok
TOperator, Text
txt) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
txt
matchOpOrOther (MyTok
TOther, Text
txt) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
txt
matchOpOrOther (MyTok, Text)
_ = Maybe Text
forall a. Maybe a
Nothing
formatToken :: (MyTok, Text) -> Text
formatToken :: (MyTok, Text) -> Text
formatToken (MyTok
TOperator,Text -> Maybe Text
unbrace -> Just Text
op) = Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (MyTok, Text) -> Text
formatToken (MyTok
TOperator, Text
op) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
formatToken (MyTok
TKeyword, Text
"forall") = Text -> Text
mathop Text
"forall"
formatToken (MyTok
TKeyword, Text
"∀" ) = Text -> Text
mathop Text
"forall"
formatToken (OpOrOther Text
"∀") = Text -> Text
mathop Text
"forall"
formatToken (MyTok
TVar, Text
"bottom") = Text -> Text
mathop Text
"bot"
formatToken (MyTok
TVar, Text
"undefined") = Text -> Text
mathop Text
"perp"
formatToken (MyTok
TVar, Text
"top" ) = Text -> Text
mathop Text
"top"
formatToken (MyTok
TVar, Text
"not" ) = Text -> Text
mathop Text
"neg"
formatToken (MyTok
TOperator,Text
">>=" ) = Text -> Text
mathop Text
"mathbin{\\gg\\!\\!=}"
formatToken (MyTok
TOperator,Text
"=<<" ) = Text -> Text
mathop Text
"mathbin{=\\!\\!<\\!\\!\\!<}"
formatToken (MyTok
TOperator,Text
">=>" ) = Text -> Text
mathop Text
"mathbin{>\\!\\!=\\!\\!\\!>}"
formatToken (MyTok
TOperator,Text
"|-" ) = Text -> Text
mathop Text
"vdash"
formatToken (MyTok
TOperator,Text
"/\\" ) = Text -> Text
mathop Text
"lor"
formatToken (MyTok
TOperator,Text
"\\/" ) = Text -> Text
mathop Text
"land"
formatToken (MyTok
TOperator,Text
"\\|/" ) = Text -> Text
mathop Text
"downarrow"
formatToken (MyTok
TOperator,Text
"\\||/" ) = Text -> Text
mathop Text
"Downarrow"
formatToken (MyTok
TOperator,Text
"/|\\" ) = Text -> Text
mathop Text
"uparrow"
formatToken (MyTok
TOperator,Text
"/||\\" ) = Text -> Text
mathop Text
"Uparrow"
formatToken (MyTok
TOperator,Text
"~>" ) = Text -> Text
mathop Text
"leadsto"
formatToken (MyTok
TOperator,Text
"|=" ) = Text -> Text
mathop Text
"models"
formatToken (MyTok
TCons ,Text
"Natural") = Text
"\\mathbb{N}"
formatToken (MyTok
TCons ,Text
"Integer") = Text
"\\mathbb{Z}"
formatToken (MyTok
TOperator,Text
"|" ) = Text -> Text
mathop Text
"alt"
formatToken (MyTok
TOperator,Text
"||" ) = Text -> Text
mathop Text
"parallel"
formatToken (MyTok
TOperator,Text
"|>" ) = Text -> Text
mathop Text
"triangleright"
formatToken (MyTok
TOperator,Text
">>" ) = Text -> Text
mathop Text
"gg"
formatToken (MyTok
TOperator,Text
">>>" ) = Text -> Text
mathop Text
"ggg"
formatToken (MyTok
TOperator,Text
"<<" ) = Text -> Text
mathop Text
"ll"
formatToken (MyTok
TOperator,Text
"<<<" ) = Text -> Text
mathop Text
"lll"
formatToken (MyTok
TOperator,Text
"\\\\" ) = Text -> Text
mathop Text
"setminus"
formatToken (OpOrOther Text
"\\") = Text -> Text
mathop Text
"lambda"
formatToken (OpOrOther Text
"λ") = Text -> Text
mathop Text
"lambda"
formatToken (MyTok
TVar, Text
"λ" ) = Text -> Text
mathop Text
"lambda"
formatToken (OpOrOther Text
"-<") = Text -> Text
mathop Text
"prec"
formatToken (OpOrOther Text
"⤙") = Text -> Text
mathop Text
"prec"
formatToken (OpOrOther Text
">-") = Text -> Text
mathop Text
"succ"
formatToken (OpOrOther Text
"⤚") = Text -> Text
mathop Text
"succ"
formatToken (OpOrOther Text
"<-") = Text -> Text
mathop Text
"gets"
formatToken (OpOrOther Text
"←") = Text -> Text
mathop Text
"gets"
formatToken (MyTok
TOperator,Text
">=" ) = Text -> Text
mathop Text
"geq"
formatToken (MyTok
TOperator,Text
"<=" ) = Text -> Text
mathop Text
"leq"
formatToken (MyTok
TOperator,Text
"!=" ) = Text -> Text
mathop Text
"ne"
formatToken (MyTok
TOperator,Text
"<->" ) = Text -> Text
mathop Text
"updownarrow"
formatToken (MyTok
TOperator,Text
"<|>" ) = Text -> Text
mathop Text
"leftrightarrow"
formatToken (OpOrOther Text
"->") = Text -> Text
mathop Text
"to"
formatToken (OpOrOther Text
"→") = Text -> Text
mathop Text
"to"
formatToken (OpOrOther Text
"=>") = Text -> Text
mathop Text
"Rightarrow"
formatToken (OpOrOther Text
"⇒") = Text -> Text
mathop Text
"Rightarrow"
formatToken (OpOrOther Text
"::") = Text -> Text
mathop Text
":"
formatToken (OpOrOther Text
"∷") = Text -> Text
mathop Text
":"
formatToken (OpOrOther Text
"*") = Text -> Text
mathop Text
"times"
formatToken (OpOrOther Text
"★") = Text -> Text
mathop Text
"star"
formatToken (OpOrOther Text
">>-") = Text -> Text
mathop Text
"rr"
formatToken (OpOrOther Text
"⤜") = Text -> Text
mathop Text
"rr"
formatToken (OpOrOther Text
"-<<") = Text -> Text
mathop Text
"ll"
formatToken (OpOrOther Text
"⤛") = Text -> Text
mathop Text
"ll"
formatToken (OpOrOther Text
"⊸") = Text -> Text
mathop Text
"multimap"
formatToken (OpOrOther Text
"(|") = Text -> Text
mathop Text
"llparenthesis"
formatToken (OpOrOther Text
"⦇") = Text -> Text
mathop Text
"llparenthesis"
formatToken (OpOrOther Text
"|)") = Text -> Text
mathop Text
"rrparenthesis"
formatToken (OpOrOther Text
"⦈") = Text -> Text
mathop Text
"rrparenthesis"
formatToken (OpOrOther Text
"[|") = Text -> Text
mathop Text
"llbracket"
formatToken (OpOrOther Text
"⟦") = Text -> Text
mathop Text
"llbracket"
formatToken (OpOrOther Text
"|]") = Text -> Text
mathop Text
"rrbracket"
formatToken (OpOrOther Text
"⟧") = Text -> Text
mathop Text
"rrbracket"
formatToken (MyTok
TOperator,Text
"==>" ) = Text -> Text
mathop Text
"implies"
formatToken (MyTok
TOperator,Text
"|->" ) = Text -> Text
mathop Text
"mapsto"
formatToken (MyTok
TOperator,Text
"|=>" ) = Text -> Text
mathop Text
"Mapsto"
formatToken (MyTok
TOperator,Text
"<>" ) = Text -> Text
mathop Text
"diamond"
formatToken (MyTok
TOperator,Text
"<$>" ) = Text -> Text
mathop Text
"mathbin{\\ooalign{\\raise.29ex\\hbox{$\\scriptscriptstyle\\$$}\\cr\\hss$\\!\\lozenge$\\hss}}"
formatToken (MyTok
TOperator,Text
"<*>" ) = Text -> Text
mathop Text
"mathbin{\\ooalign{\\raise.37ex\\hbox{$\\scriptscriptstyle{*}$}\\cr\\hss$\\!\\lozenge$\\hss}}"
formatToken (MyTok
TOperator,Text
"elem" ) = Text -> Text
mathop Text
"in"
formatToken (MyTok
TOperator,Text
"~" ) = Text -> Text
mathop Text
"sim"
formatToken (MyTok
TOperator,Text
"~=" ) = Text -> Text
mathop Text
"approx"
formatToken (MyTok
TOperator,Text
"><" ) = Text -> Text
mathop Text
"times"
formatToken (MyTok
TOperator,Text
":->" ) = Text -> Text
mathop Text
"longmapsto"
formatToken (MyTok
TVar, Text
"a" ) = Text -> Text
mathop Text
"alpha"
formatToken (MyTok
TVar, Text
"b" ) = Text -> Text
mathop Text
"beta"
formatToken (MyTok
TVar, Text
"c" ) = Text -> Text
mathop Text
"gamma"
formatToken (MyTok
TVar, Text
"d" ) = Text -> Text
mathop Text
"delta"
formatToken (MyTok
TVar, Text
"eps" ) = Text -> Text
mathop Text
"epsilon"
formatToken (MyTok
TVar, Text
"k" ) = Text -> Text
mathop Text
"kappa"
formatToken (MyTok
TVar, Text
"n" ) = Text -> Text
mathop Text
"nu"
formatToken (MyTok
TVar, Text
"m" ) = Text -> Text
mathop Text
"mu"
formatToken (MyTok
TVar, Text
"sigma" ) = Text -> Text
mathop Text
"sigma"
formatToken (MyTok
TVar, Text
"omega" ) = Text -> Text
mathop Text
"omega"
formatToken (MyTok
TVar, Text
"pi" ) = Text -> Text
mathop Text
"pi"
formatToken (MyTok
TVar, Text
"tau" ) = Text -> Text
mathop Text
"tau"
formatToken (MyTok
TVar, Text
"rho" ) = Text -> Text
mathop Text
"rho"
formatToken (MyTok
TVar , Text
txt ) | (Char -> Bool) -> Text -> Bool
T.any Char -> Bool
isAlpha Text
txt = Text
"\\textit{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
subAndSuperscripts Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
formatToken (MyTok
TVar, Text
txt ) = Text
"\\textit{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
protectText Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
formatToken (MyTok
TNum , Text
kwd ) = Text -> Text
protectText Text
kwd
formatToken (MyTok
TKeyword, Text
kwd ) = Text
"\\textbf{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
protectText Text
kwd Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
formatToken (MyTok
TCons, Text
cons ) = Text
"\\textsc{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
subAndSuperscripts Text
cons Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
formatToken (TTikz Text
mark,Text
_ ) = Text -> Text
mathop (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
"tikzMark{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
mark Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
formatToken (MyTok
TOther, Text
"`" ) = Text -> Text
protectText Text
"`"
formatToken (MyTok
TOther, Text
"'" ) = Text -> Text
mathop Text
"prime"
formatToken (MyTok
TOther, Text
"\"" ) = Text -> Text
protectText Text
"\""
formatToken (MyTok
TOther, Text
"(" ) = Text -> Text
protectText Text
"("
formatToken (MyTok
TOther, Text
")" ) = Text -> Text
protectText Text
")"
formatToken (MyTok
TOther, Text
"]" ) = Text -> Text
protectText Text
"]"
formatToken (MyTok
TOther, Text
"[" ) = Text -> Text
protectText Text
"["
formatToken (MyTok
TOther, Text
"}" ) = Text -> Text
protectText Text
"}"
formatToken (MyTok
TOther, Text
"{" ) = Text -> Text
protectText Text
"{"
formatToken (MyTok
TOther, Text
"=" ) = Text
"=\\joinrel="
formatToken (MyTok
_, Text
txt ) = Text
"\\textrm{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
protectTextMath Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
mathop :: Text -> Text
mathop :: Text -> Text
mathop Text
code = Text
"\\" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
code
prologue :: Text
prologue :: Text
prologue = [Text] -> Text
T.concat [Text
"\\usepackage{amssymb}"]
latexPackages :: [Text]
latexPackages :: [Text]
latexPackages = [Text
"amssymb", Text
"amsmath", Text
"stmaryrd"]