{-# LANGUAGE GeneralizedNewtypeDeriving, ViewPatterns, GADTs, OverloadedStrings #-}
module Text.TeXMath.Writers.Typst (writeTypst) where
import Data.List (transpose)
import qualified Data.Map as M
import qualified Data.Text as T
import Text.TeXMath.Types
import qualified Text.TeXMath.Shared as S
import Typst.Symbols (typstSymbols)
import Data.Generics (everywhere, mkT)
import Data.Text (Text)
import Data.Char (isDigit, isAlpha)
writeTypst :: DisplayType -> [Exp] -> Text
writeTypst :: DisplayType -> [Exp] -> Text
writeTypst DisplayType
dt [Exp]
exprs =
[Text] -> Text
T.unwords forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Exp -> Text
writeExp forall a b. (a -> b) -> a -> b
$ (forall a. Data a => a -> a) -> forall a. Data a => a -> a
everywhere (forall a b. (Typeable a, Typeable b) => (b -> b) -> a -> a
mkT forall a b. (a -> b) -> a -> b
$ DisplayType -> Exp -> Exp
S.handleDownup DisplayType
dt) [Exp]
exprs
writeExps :: [Exp] -> Text
writeExps :: [Exp] -> Text
writeExps = Text -> [Text] -> Text
T.intercalate Text
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Exp -> Text
writeExp
inParens :: Text -> Text
inParens :: Text -> Text
inParens Text
s = Text
"(" forall a. Semigroup a => a -> a -> a
<> Text
s forall a. Semigroup a => a -> a -> a
<> Text
")"
inQuotes :: Text -> Text
inQuotes :: Text -> Text
inQuotes Text
s = Text
"\"" forall a. Semigroup a => a -> a -> a
<> Text
s forall a. Semigroup a => a -> a -> a
<> Text
"\""
esc :: Text -> Text
esc :: Text -> Text
esc Text
t =
if (Char -> Bool) -> Text -> Bool
T.any Char -> Bool
needsEscape Text
t
then (Char -> Text) -> Text -> Text
T.concatMap Char -> Text
escapeChar Text
t
else Text
t
where
escapeChar :: Char -> Text
escapeChar Char
c
| Char -> Bool
needsEscape Char
c = Text
"\\" forall a. Semigroup a => a -> a -> a
<> Char -> Text
T.singleton Char
c
| Bool
otherwise = Char -> Text
T.singleton Char
c
needsEscape :: Char -> Bool
needsEscape Char
'[' = Bool
True
needsEscape Char
']' = Bool
True
needsEscape Char
'|' = Bool
True
needsEscape Char
'#' = Bool
True
needsEscape Char
'$' = Bool
True
needsEscape Char
'(' = Bool
True
needsEscape Char
')' = Bool
True
needsEscape Char
'_' = Bool
True
needsEscape Char
_ = Bool
False
writeExpS :: Exp -> Text
writeExpS :: Exp -> Text
writeExpS (EGrouped [Exp]
es) = Text
"(" forall a. Semigroup a => a -> a -> a
<> [Exp] -> Text
writeExps [Exp]
es forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExpS Exp
e =
case Exp -> Text
writeExp Exp
e of
Text
t | (Char -> Bool) -> Text -> Bool
T.all (\Char
c -> Char -> Bool
isDigit Char
c Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'.') Text
t -> Text
t
| (Char -> Bool) -> Text -> Bool
T.all (\Char
c -> Char -> Bool
isAlpha Char
c Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'.') Text
t -> Text
t
| Bool
otherwise -> Text
"(" forall a. Semigroup a => a -> a -> a
<> Text
t forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExpB :: Exp -> Text
writeExpB :: Exp -> Text
writeExpB Exp
e =
case Exp -> Text
writeExp Exp
e of
Text
"" -> Text
"zws"
Text
t -> Text
t
writeExp :: Exp -> Text
writeExp :: Exp -> Text
writeExp (ENumber Text
s) = Text
s
writeExp (ESymbol TeXSymbolType
_t Text
s) =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> Text
esc Text
s) forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
s Map Text Text
typstSymbolMap
writeExp (EIdentifier Text
s) =
if Text -> Int
T.length Text
s forall a. Eq a => a -> a -> Bool
== Int
1
then Exp -> Text
writeExp (TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
s)
else Text -> Text
inQuotes Text
s
writeExp (EMathOperator Text
s)
| Text
s forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"arccos", Text
"arcsin", Text
"arctan", Text
"arg", Text
"cos", Text
"cosh",
Text
"cot", Text
"ctg", Text
"coth", Text
"csc", Text
"deg", Text
"det", Text
"dim", Text
"exp",
Text
"gcd", Text
"hom", Text
"mod", Text
"inf", Text
"ker", Text
"lg", Text
"lim", Text
"ln",
Text
"log", Text
"max", Text
"min", Text
"Pr", Text
"sec", Text
"sin", Text
"sinh", Text
"sup",
Text
"tan", Text
"tg", Text
"tanh", Text
"liminf", Text
"and", Text
"limsup"]
= Text
s
| Bool
otherwise = Text
"\"" forall a. Semigroup a => a -> a -> a
<> Text
s forall a. Semigroup a => a -> a -> a
<> Text
"\""
writeExp (EGrouped [Exp]
es) = [Exp] -> Text
writeExps [Exp]
es
writeExp (EFraction FractionType
_fractype Exp
e1 Exp
e2) =
case (Exp
e1, Exp
e2) of
(EGrouped [Exp]
_, Exp
_) -> Text
"frac(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e2 forall a. Semigroup a => a -> a -> a
<> Text
")"
(Exp
_, EGrouped [Exp]
_) -> Text
"frac(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e2 forall a. Semigroup a => a -> a -> a
<> Text
")"
(Exp, Exp)
_ -> Exp -> Text
writeExp Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
" / " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e2
writeExp (ESub Exp
b Exp
e1) = Exp -> Text
writeExpB Exp
b forall a. Semigroup a => a -> a -> a
<> Text
"_" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e1
writeExp (ESuper Exp
b Exp
e1) = Exp -> Text
writeExpB Exp
b forall a. Semigroup a => a -> a -> a
<> Text
"^" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e1
writeExp (ESubsup Exp
b Exp
e1 Exp
e2) = Exp -> Text
writeExpB Exp
b forall a. Semigroup a => a -> a -> a
<> Text
"_" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e1 forall a. Semigroup a => a -> a -> a
<>
Text
"^" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e2
writeExp (EOver Bool
_ (EOver Bool
_ Exp
b (ESymbol TeXSymbolType
TOver Text
"\9182")) Exp
e1) =
Text
"overbrace(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EOver Bool
_ (EOver Bool
_ Exp
b (ESymbol TeXSymbolType
TOver Text
"\9140")) Exp
e1) =
Text
"overbracket(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EOver Bool
_convertible Exp
b Exp
e1) =
case Exp
e1 of
ESymbol TeXSymbolType
Accent Text
"`" -> Text
"grave" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\768" -> Text
"grave" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\xb4" -> Text
"acute" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"^" -> Text
"hat" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\770" -> Text
"hat" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"~" -> Text
"tilde" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\771" -> Text
"tilde" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\xaf" -> Text
"macron" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\x2d8" -> Text
"breve" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"." -> Text
"dot" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\775" -> Text
"dot" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\xa8" -> Text
"diaer" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\x2218" -> Text
"circle" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\x2dd" -> Text
"acute.double" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\x2c7" -> Text
"caron" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\x2192" -> Text
"->" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
Accent Text
"\x2190" -> Text
"<-" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Exp -> Text
writeExp Exp
b)
ESymbol TeXSymbolType
TOver Text
"\9182" -> Text
"overbrace(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
")"
ESymbol TeXSymbolType
TOver Text
"\9140" -> Text
"overbracket(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
")"
ESymbol TeXSymbolType
TOver Text
"\175" -> Text
"overline(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
")"
Exp
_ -> Exp -> Text
writeExpB Exp
b forall a. Semigroup a => a -> a -> a
<> Text
"^" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e1
writeExp (EUnder Bool
_ (EUnder Bool
_ Exp
b (ESymbol TeXSymbolType
TUnder Text
"\9183")) Exp
e1) =
Text
"underbrace(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EUnder Bool
_ (EUnder Bool
_ Exp
b (ESymbol TeXSymbolType
TUnder Text
"\9140")) Exp
e1) =
Text
"underbrace(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EUnder Bool
_convertible Exp
b Exp
e1) =
case Exp
e1 of
ESymbol TeXSymbolType
TUnder Text
"_" -> Text
"underline(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
")"
ESymbol TeXSymbolType
TUnder Text
"\9183" -> Text
"underbrace(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
")"
ESymbol TeXSymbolType
TUnder Text
"\9140" -> Text
"underbracket(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
b forall a. Semigroup a => a -> a -> a
<> Text
")"
Exp
_ -> Exp -> Text
writeExpB Exp
b forall a. Semigroup a => a -> a -> a
<> Text
"_" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e1
writeExp (EUnderover Bool
convertible Exp
b Exp
e1 Exp
e2) =
case (Exp
e1, Exp
e2) of
(Exp
_, ESymbol TeXSymbolType
Accent Text
_) -> Exp -> Text
writeExp (Bool -> Exp -> Exp -> Exp
EUnder Bool
convertible (Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
b Exp
e2) Exp
e1)
(Exp
_, ESymbol TeXSymbolType
TOver Text
_) -> Exp -> Text
writeExp (Bool -> Exp -> Exp -> Exp
EUnder Bool
convertible (Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
b Exp
e2) Exp
e1)
(ESymbol TeXSymbolType
TUnder Text
_, Exp
_) -> Exp -> Text
writeExp (Bool -> Exp -> Exp -> Exp
EOver Bool
convertible (Bool -> Exp -> Exp -> Exp
EUnder Bool
False Exp
b Exp
e1) Exp
e2)
(Exp, Exp)
_ -> Exp -> Text
writeExpB Exp
b forall a. Semigroup a => a -> a -> a
<> Text
"_" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e1 forall a. Semigroup a => a -> a -> a
<> Text
"^" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExpS Exp
e2
writeExp (ESqrt Exp
e) = Text
"sqrt(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (ERoot Exp
i Exp
e) = Text
"root(" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
i forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (ESpace Rational
width) =
case (forall a b. (RealFrac a, Integral b) => a -> b
floor (Rational
width forall a. Num a => a -> a -> a
* Rational
18) :: Int) of
Int
0 -> Text
"zws"
Int
3 -> Text
"thin"
Int
4 -> Text
"med"
Int
6 -> Text
"thick"
Int
18 -> Text
"quad"
Int
n -> Text
"#h(" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
tshow (Int
n forall a. Integral a => a -> a -> a
`div` Int
18) forall a. Semigroup a => a -> a -> a
<> Text
"em)"
writeExp (EText TextType
ttype Text
s) =
case TextType
ttype of
TextType
TextNormal -> Text
"upright" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextItalic -> Text
"italic" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextBold -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextBoldItalic -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"italic" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s))
TextType
TextMonospace -> Text
"mono" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextSansSerif -> Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextDoubleStruck -> Text
"bb" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextScript -> Text
"cal" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextFraktur -> Text
"frak" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)
TextType
TextSansSerifBold -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s))
TextType
TextSansSerifBoldItalic -> Text
"bold" forall a. Semigroup a => a -> a -> a
<>
Text -> Text
inParens (Text
"italic" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s)))
TextType
TextBoldScript -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"cal" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s))
TextType
TextBoldFraktur -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"frak" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s))
TextType
TextSansSerifItalic -> Text
"italic" forall a. Semigroup a => a -> a -> a
<>
Text -> Text
inParens (Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text -> Text
inQuotes Text
s))
writeExp (EStyled TextType
ttype [Exp]
es) =
let contents :: Text
contents = [Exp] -> Text
writeExps [Exp]
es
in case TextType
ttype of
TextType
TextNormal -> Text
"upright" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextItalic -> Text
"italic" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextBold -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextBoldItalic -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"italic" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents)
TextType
TextMonospace -> Text
"mono" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextSansSerif -> Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextDoubleStruck -> Text
"bb" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextScript -> Text
"cal" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextFraktur -> Text
"frak" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents
TextType
TextSansSerifBold -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents)
TextType
TextSansSerifBoldItalic -> Text
"bold" forall a. Semigroup a => a -> a -> a
<>
Text -> Text
inParens (Text
"italic" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents))
TextType
TextBoldScript -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"cal" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents)
TextType
TextBoldFraktur -> Text
"bold" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"frak" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents)
TextType
TextSansSerifItalic -> Text
"italic" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
"sans" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens Text
contents)
writeExp (EBoxed Exp
e) = Text
"#box([" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e forall a. Semigroup a => a -> a -> a
<> Text
"])"
writeExp (EPhantom Exp
e) = Text
"#hide[" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e forall a. Semigroup a => a -> a -> a
<> Text
"]"
writeExp (EScaled Rational
size Exp
e) =
Text
"#scale(x: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
tshow (forall a b. (RealFrac a, Integral b) => a -> b
floor (Rational
100 forall a. Num a => a -> a -> a
* Rational
size) :: Int) forall a. Semigroup a => a -> a -> a
<>
Text
"%, y: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
tshow (forall a b. (RealFrac a, Integral b) => a -> b
floor (Rational
100 forall a. Num a => a -> a -> a
* Rational
size) :: Int) forall a. Semigroup a => a -> a -> a
<>
Text
"%)[" forall a. Semigroup a => a -> a -> a
<> Exp -> Text
writeExp Exp
e forall a. Semigroup a => a -> a -> a
<> Text
"]"
writeExp (EDelimited Text
"(" Text
")" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)])
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\ArrayLine
row -> forall (t :: * -> *) a. Foldable t => t a -> Int
length ArrayLine
row forall a. Eq a => a -> a -> Bool
== Int
1) [ArrayLine]
rows =
Text
"vec(" forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray (forall a. [[a]] -> [[a]]
transpose [ArrayLine]
rows) forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"(" Text
")" [Right (EArray [Alignment]
_aligns [[[Exp]
xs],[[Exp]
ys]])]) =
Text
"binom(" forall a. Semigroup a => a -> a -> a
<> [Exp] -> Text
writeExps [Exp]
xs forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> [Exp] -> Text
writeExps [Exp]
ys forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"(" Text
")" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)]) =
Text
"mat(delim: \"(\", " forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray [ArrayLine]
rows forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"[" Text
"]" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)]) =
Text
"mat(delim: \"[\", " forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray [ArrayLine]
rows forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"{" Text
"}" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)]) =
Text
"mat(delim: \"{\", " forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray [ArrayLine]
rows forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"|" Text
"|" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)]) =
Text
"mat(delim: \"|\", " forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray [ArrayLine]
rows forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"||" Text
"||" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)]) =
Text
"mat(delim: \"||\", " forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray [ArrayLine]
rows forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"\x2223" Text
"\x2223" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)]) =
Text
"mat(delim: \"||\", " forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray [ArrayLine]
rows forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
"\x2225" Text
"\x2225" [Right (EArray [Alignment]
_aligns [ArrayLine]
rows)]) =
Text
"mat(delim: \"||\", " forall a. Semigroup a => a -> a -> a
<> [ArrayLine] -> Text
mkArray [ArrayLine]
rows forall a. Semigroup a => a -> a -> a
<> Text
")"
writeExp (EDelimited Text
op Text
"" [Right (EArray [Alignment
AlignLeft, Alignment
AlignLeft] [ArrayLine]
rows)]) =
Text
"cases" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens(Text
"delim: " forall a. Semigroup a => a -> a -> a
<> Text -> Text
inQuotes Text
op forall a. Semigroup a => a -> a -> a
<> forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map ArrayLine -> Text
toCase [ArrayLine]
rows))
where toCase :: ArrayLine -> Text
toCase = (Text
", " forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
" & " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map [Exp] -> Text
writeExps
writeExp (EDelimited Text
open Text
close [InEDelimited]
es) =
if forall {a}. (Eq a, IsString a) => a -> Bool
isDelim Text
open Bool -> Bool -> Bool
&& forall {a}. (Eq a, IsString a) => a -> Bool
isDelim Text
close
then Text
"lr" forall a. Semigroup a => a -> a -> a
<> Text -> Text
inParens (Text
open forall a. Semigroup a => a -> a -> a
<> Text
body forall a. Semigroup a => a -> a -> a
<> Text
close)
else Text -> Text
esc Text
open forall a. Semigroup a => a -> a -> a
<> Text
body forall a. Semigroup a => a -> a -> a
<> Text -> Text
esc Text
close
where fromDelimited :: InEDelimited -> Text
fromDelimited (Left Text
e) = Text
e
fromDelimited (Right Exp
e) = Exp -> Text
writeExp Exp
e
isDelim :: a -> Bool
isDelim a
c = a
c forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a
"(",a
")",a
"[",a
"]",a
"{",a
"}",a
"|",a
"||"]
body :: Text
body = [Text] -> Text
T.unwords (forall a b. (a -> b) -> [a] -> [b]
map InEDelimited -> Text
fromDelimited [InEDelimited]
es)
writeExp (EArray [Alignment]
_aligns [ArrayLine]
rows)
= Text -> [Text] -> Text
T.intercalate Text
"\\\n" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ArrayLine -> Text
mkRow [ArrayLine]
rows
where mkRow :: ArrayLine -> Text
mkRow = Text -> [Text] -> Text
T.intercalate Text
" & " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map [Exp] -> Text
writeExps
mkArray :: [[[Exp]]] -> Text
mkArray :: [ArrayLine] -> Text
mkArray [ArrayLine]
rows =
Text -> [Text] -> Text
T.intercalate Text
"; " forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ArrayLine -> Text
mkRow [ArrayLine]
rows
where
mkRow :: ArrayLine -> Text
mkRow = Text -> [Text] -> Text
T.intercalate Text
", " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map [Exp] -> Text
mkCell
mkCell :: [Exp] -> Text
mkCell = [Exp] -> Text
writeExps
tshow :: Show a => a -> Text
tshow :: forall a. Show a => a -> Text
tshow = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
typstSymbolMap :: M.Map Text Text
typstSymbolMap :: Map Text Text
typstSymbolMap = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Text
s,Text
name) | (Text
name, Bool
_, Text
s) <- [(Text, Bool, Text)]
typstSymbols]