{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.TeXMath.Readers.TeX (readTeX)
where
import Data.List (intercalate, intersperse, find)
import Data.Ratio ((%))
import Control.Monad
import Data.Char (isDigit, isAscii, isLetter)
import qualified Data.Map as M
import qualified Data.Text as T
import Data.Text (Text)
import Data.Maybe (mapMaybe, catMaybes)
import Data.Semigroup ((<>))
import Text.Parsec hiding (label)
import Text.Parsec.Error
import Text.Parsec.Text
import Text.TeXMath.Types
import Data.Functor (($>))
import Control.Applicative ((<*), (*>), (<*>), (<$>), (<$), pure)
import qualified Text.TeXMath.Shared as S
import Text.TeXMath.Readers.TeX.Macros (applyMacros, parseMacroDefinitions)
import Text.TeXMath.Unicode.ToTeX (getSymbolType)
import Data.Maybe (fromJust)
import Text.TeXMath.Unicode.ToUnicode (toUnicode)
import Text.TeXMath.Shared (getSpaceChars)
import Data.Generics (everywhere, mkT)
type TP = Parser
expr1 :: TP Exp
expr1 :: TP Exp
expr1 = [TP Exp] -> TP Exp
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ TP Exp
inbraces
, TP Exp
variable
, TP Exp
number
, TP Exp
unicode
, TP Exp
operator
, TP Exp
bareSubSup
, TP Exp
enclosure
, TP Exp
command
] TP Exp -> ParsecT Text () Identity () -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
ignorable
readTeX :: Text -> Either Text [Exp]
readTeX :: Text -> Either Text [Exp]
readTeX Text
inp =
let ([Macro]
ms, Text
rest) = Text -> ([Macro], Text)
parseMacroDefinitions Text
inp in
(ParseError -> Either Text [Exp])
-> ([Exp] -> Either Text [Exp])
-> Either ParseError [Exp]
-> Either Text [Exp]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Either Text [Exp]
forall a b. a -> Either a b
Left (Text -> Either Text [Exp])
-> (ParseError -> Text) -> ParseError -> Either Text [Exp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ParseError -> Text
showParseError Text
inp) ([Exp] -> Either Text [Exp]
forall a b. b -> Either a b
Right ([Exp] -> Either Text [Exp])
-> ([Exp] -> [Exp]) -> [Exp] -> Either Text [Exp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Data a => a -> a) -> forall a. Data a => a -> a
everywhere ((Exp -> Exp) -> a -> a
forall a b. (Typeable a, Typeable b) => (b -> b) -> a -> a
mkT Exp -> Exp
fixBins))
(Either ParseError [Exp] -> Either Text [Exp])
-> Either ParseError [Exp] -> Either Text [Exp]
forall a b. (a -> b) -> a -> b
$ Parsec Text () [Exp]
-> SourceName -> Text -> Either ParseError [Exp]
forall s t a.
Stream s Identity t =>
Parsec s () a -> SourceName -> s -> Either ParseError a
parse Parsec Text () [Exp]
formula SourceName
"formula" (Text -> Either ParseError [Exp])
-> Text -> Either ParseError [Exp]
forall a b. (a -> b) -> a -> b
$ [Macro] -> Text -> Text
applyMacros [Macro]
ms Text
rest
fixBins :: Exp -> Exp
fixBins :: Exp -> Exp
fixBins Exp
e =
case Exp
e of
EGrouped [Exp]
es -> [Exp] -> Exp
EGrouped (Bool -> [Exp] -> [Exp]
fixBinList Bool
True [Exp]
es)
EDelimited Text
op Text
cl [InEDelimited]
des -> Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
op Text
cl (Bool -> [InEDelimited] -> [InEDelimited]
forall a. Bool -> [Either a Exp] -> [Either a Exp]
fixBinListDel Bool
True [InEDelimited]
des)
Exp
_ -> Exp
e
where
fixBinList :: Bool -> [Exp] -> [Exp]
fixBinList Bool
atBeginning [Exp]
xs =
case [Exp]
xs of
ESymbol TeXSymbolType
Bin Text
t : [Exp]
rest
| Bool
atBeginning
-> TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
t Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: Bool -> [Exp] -> [Exp]
fixBinList Bool
False [Exp]
rest
ESymbol TeXSymbolType
Bin Text
t : rest :: [Exp]
rest@(ESymbol TeXSymbolType
ty Text
_ : [Exp]
_)
| TeXSymbolType
ty TeXSymbolType -> TeXSymbolType -> Bool
forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Open Bool -> Bool -> Bool
|| TeXSymbolType
ty TeXSymbolType -> TeXSymbolType -> Bool
forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Pun Bool -> Bool -> Bool
|| TeXSymbolType
ty TeXSymbolType -> TeXSymbolType -> Bool
forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Op
-> TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
t Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: Bool -> [Exp] -> [Exp]
fixBinList Bool
False [Exp]
rest
Exp
x:[Exp]
rest -> Exp
x Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
: Bool -> [Exp] -> [Exp]
fixBinList Bool
False [Exp]
rest
[] -> []
fixBinListDel :: Bool -> [Either a Exp] -> [Either a Exp]
fixBinListDel Bool
atBeginning [Either a Exp]
xs =
case [Either a Exp]
xs of
Left a
x : [Either a Exp]
rest
-> a -> Either a Exp
forall a b. a -> Either a b
Left a
x Either a Exp -> [Either a Exp] -> [Either a Exp]
forall a. a -> [a] -> [a]
: Bool -> [Either a Exp] -> [Either a Exp]
fixBinListDel Bool
True [Either a Exp]
rest
Right (ESymbol TeXSymbolType
Bin Text
t) : [Either a Exp]
rest
| Bool
atBeginning
-> Exp -> Either a Exp
forall a b. b -> Either a b
Right (TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
t) Either a Exp -> [Either a Exp] -> [Either a Exp]
forall a. a -> [a] -> [a]
: Bool -> [Either a Exp] -> [Either a Exp]
fixBinListDel Bool
False [Either a Exp]
rest
Right (ESymbol TeXSymbolType
Bin Text
t) : rest :: [Either a Exp]
rest@(Right (ESymbol TeXSymbolType
ty Text
_):[Either a Exp]
_)
| TeXSymbolType
ty TeXSymbolType -> TeXSymbolType -> Bool
forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Open Bool -> Bool -> Bool
|| TeXSymbolType
ty TeXSymbolType -> TeXSymbolType -> Bool
forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Pun Bool -> Bool -> Bool
|| TeXSymbolType
ty TeXSymbolType -> TeXSymbolType -> Bool
forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Op
-> Exp -> Either a Exp
forall a b. b -> Either a b
Right (TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
t) Either a Exp -> [Either a Exp] -> [Either a Exp]
forall a. a -> [a] -> [a]
: Bool -> [Either a Exp] -> [Either a Exp]
fixBinListDel Bool
False [Either a Exp]
rest
Either a Exp
x:[Either a Exp]
rest -> Either a Exp
x Either a Exp -> [Either a Exp] -> [Either a Exp]
forall a. a -> [a] -> [a]
: Bool -> [Either a Exp] -> [Either a Exp]
fixBinListDel Bool
False [Either a Exp]
rest
[] -> []
showParseError :: Text -> ParseError -> Text
showParseError :: Text -> ParseError -> Text
showParseError Text
inp ParseError
pe =
Text
snippet Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
caretline Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
SourceName -> Text
T.pack (SourceName
-> SourceName
-> SourceName
-> SourceName
-> SourceName
-> [Message]
-> SourceName
showErrorMessages SourceName
"or" SourceName
"unknown" SourceName
"expecting" SourceName
"unexpected" SourceName
"eof"
(ParseError -> [Message]
errorMessages ParseError
pe))
where errln :: Line
errln = SourcePos -> Line
sourceLine (ParseError -> SourcePos
errorPos ParseError
pe)
errcol :: Line
errcol = SourcePos -> Line
sourceColumn (ParseError -> SourcePos
errorPos ParseError
pe)
snipoffset :: Line
snipoffset = Line -> Line -> Line
forall a. Ord a => a -> a -> a
max Line
0 (Line
errcol Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
20)
inplns :: [Text]
inplns = Text -> [Text]
T.lines Text
inp
ln :: Text
ln = if [Text] -> Line
forall (t :: * -> *) a. Foldable t => t a -> Line
length [Text]
inplns Line -> Line -> Bool
forall a. Ord a => a -> a -> Bool
>= Line
errln
then [Text]
inplns [Text] -> Line -> Text
forall a. [a] -> Line -> a
!! (Line
errln Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
1)
else Text
""
snippet :: Text
snippet = Line -> Text -> Text
T.take Line
40 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Line -> Text -> Text
T.drop Line
snipoffset Text
ln
caretline :: Text
caretline = Line -> Text -> Text
T.replicate (Line
errcol Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
snipoffset Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
1) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"^"
anyCtrlSeq :: TP Text
anyCtrlSeq :: TP Text
anyCtrlSeq = TP Text -> TP Text
forall a. TP a -> TP a
lexeme (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\'
SourceName
res <- Line
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
Line -> ParsecT s u m a -> ParsecT s u m [a]
count Line
1 ((Char -> Bool) -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isLetter)) ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool) -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isLetter)
Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TP Text) -> Text -> TP Text
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$ Char
'\\' Char -> SourceName -> SourceName
forall a. a -> [a] -> [a]
: SourceName
res
ctrlseq :: String -> TP String
ctrlseq :: SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
s = ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a. TP a -> TP a
lexeme (ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName)
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName)
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a b. (a -> b) -> a -> b
$ do
SourceName
result <- SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string (Char
'\\'Char -> SourceName -> SourceName
forall a. a -> [a] -> [a]
:SourceName
s)
case SourceName
s of
[Char
c] | Bool -> Bool
not (Char -> Bool
isLetter Char
c) -> () -> ParsecT Text () Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
SourceName
_ -> (do SourcePos
pos <- ParsecT Text () Identity SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter
SourcePos -> ParsecT Text () Identity ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
pos
ParsecT Text () Identity ()
forall (m :: * -> *) a. MonadPlus m => m a
mzero ParsecT Text () Identity ()
-> SourceName -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> SourceName -> ParsecT s u m a
<?> (SourceName
"non-letter after \\" SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ SourceName
s))
ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () -> ParsecT Text () Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
SourceName -> ParsecT Text () Identity SourceName
forall (m :: * -> *) a. Monad m => a -> m a
return SourceName
result
ignorable :: TP ()
ignorable :: ParsecT Text () Identity ()
ignorable = ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT Text () Identity () -> ParsecT Text () Identity ())
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$
ParsecT Text () Identity ()
comment
ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text () Identity ()
label
ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text () Identity ()
tag
ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"nonumber"
ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
space ParsecT Text () Identity ()
-> SourceName -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> SourceName -> ParsecT s u m a
<?> SourceName
"whitespace")
comment :: TP ()
= Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'%' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
"\n") ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
newline
label :: TP ()
label :: ParsecT Text () Identity ()
label = SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"label" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a. TP a -> TP a
braces (ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
"}"))
tag :: TP ()
tag :: ParsecT Text () Identity ()
tag = SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"tag" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a. TP a -> TP a
braces (ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
"}"))
unGrouped :: Exp -> [Exp]
unGrouped :: Exp -> [Exp]
unGrouped (EGrouped [Exp]
xs) = [Exp]
xs
unGrouped Exp
x = [Exp
x]
formula :: TP [Exp]
formula :: Parsec Text () [Exp]
formula = Exp -> [Exp]
unGrouped (Exp -> [Exp]) -> TP Exp -> Parsec Text () [Exp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Text () Identity ()
ignorable ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP Exp -> TP Exp
manyExp TP Exp
expr TP Exp -> ParsecT Text () Identity () -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
expr :: TP Exp
expr :: TP Exp
expr = do
ParsecT Text () Identity SourceName -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"displaystyle" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"textstyle" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"scriptstyle" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"scriptscriptstyle")
(Exp
a, Bool
convertible) <- ParsecT Text () Identity (Exp, Bool)
-> ParsecT Text () Identity (Exp, Bool)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity (Exp, Bool)
-> ParsecT Text () Identity (Exp, Bool)
forall a. TP a -> TP a
braces ParsecT Text () Identity (Exp, Bool)
operatorname)
ParsecT Text () Identity (Exp, Bool)
-> ParsecT Text () Identity (Exp, Bool)
-> ParsecT Text () Identity (Exp, Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text () Identity (Exp, Bool)
operatorname
ParsecT Text () Identity (Exp, Bool)
-> ParsecT Text () Identity (Exp, Bool)
-> ParsecT Text () Identity (Exp, Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((,Bool
False) (Exp -> (Exp, Bool))
-> TP Exp -> ParsecT Text () Identity (Exp, Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
expr1)
Maybe Bool
limits <- TP (Maybe Bool)
limitsIndicator
Maybe Bool -> Bool -> Exp -> TP Exp
subSup Maybe Bool
limits Bool
convertible Exp
a TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Bool -> Bool -> Exp -> TP Exp
superOrSubscripted Maybe Bool
limits Bool
convertible Exp
a TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
a
command :: TP Exp
command :: TP Exp
command = TP Exp -> TP Exp
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
Text
c <- TP Text
anyCtrlSeq
Bool -> ParsecT Text () Identity ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Text () Identity ())
-> Bool -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ Text
c Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"\\end"
Bool -> Bool -> Bool
&& Text
c Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"\\operatorname"
[TP Exp] -> TP Exp
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ Text -> TP Exp
text Text
c
, Text -> TP Exp
styled Text
c
, Text -> TP Exp
root Text
c
, Text -> TP Exp
xspace Text
c
, Text -> TP Exp
mathop Text
c
, Text -> TP Exp
phantom Text
c
, Text -> TP Exp
boxed Text
c
, Text -> TP Exp
binary Text
c
, Text -> TP Exp
genfrac Text
c
, Text -> TP Exp
substack Text
c
, Text -> TP Exp
environment Text
c
, Text -> TP Exp
ensuremath Text
c
, Text -> TP Exp
scaled Text
c
, Text -> TP Exp
negated Text
c
, Text -> TP Exp
siunitx Text
c
, Text -> TP Exp
tSymbol Text
c
] TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> SourceName -> TP Exp
forall s (m :: * -> *) t u a.
Stream s m t =>
SourceName -> ParsecT s u m a
unexpected (SourceName
"control sequence " SourceName -> SourceName -> SourceName
forall a. Semigroup a => a -> a -> a
<> Text -> SourceName
T.unpack Text
c)
operatorname :: TP (Exp, Bool)
operatorname :: ParsecT Text () Identity (Exp, Bool)
operatorname = do
SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"operatorname"
Bool
convertible <- (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'*' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity ()
-> ParsecT Text () Identity Bool -> ParsecT Text () Identity Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT Text () Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True) ParsecT Text () Identity Bool
-> ParsecT Text () Identity Bool -> ParsecT Text () Identity Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Text () Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Maybe Text
op <- Exp -> Maybe Text
expToOperatorName (Exp -> Maybe Text)
-> TP Exp -> ParsecT Text () Identity (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken
ParsecT Text () Identity (Exp, Bool)
-> (Text -> ParsecT Text () Identity (Exp, Bool))
-> Maybe Text
-> ParsecT Text () Identity (Exp, Bool)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ParsecT Text () Identity (Exp, Bool)
forall (m :: * -> *) a. MonadPlus m => m a
mzero (\Text
s -> (Exp, Bool) -> ParsecT Text () Identity (Exp, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Exp
EMathOperator Text
s, Bool
convertible)) Maybe Text
op
expToOperatorName :: Exp -> Maybe Text
expToOperatorName :: Exp -> Maybe Text
expToOperatorName Exp
e = case Exp
e of
EGrouped [Exp]
xs -> [Text] -> Text
T.concat ([Text] -> Text) -> Maybe [Text] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Exp -> Maybe Text) -> [Exp] -> Maybe [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Exp -> Maybe Text
fl [Exp]
xs
Exp
_ -> Exp -> Maybe Text
fl Exp
e
where fl :: Exp -> Maybe Text
fl Exp
f = case Exp
f of
EIdentifier Text
s -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s
ESymbol TeXSymbolType
_ Text
"\x2212" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"-"
ESymbol TeXSymbolType
_ Text
"\x2032" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"'"
ESymbol TeXSymbolType
_ Text
"\x2033" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"''"
ESymbol TeXSymbolType
_ Text
"\x2034" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"'''"
ESymbol TeXSymbolType
_ Text
"\x2057" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"''''"
ESymbol TeXSymbolType
_ Text
"\x02B9" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"'"
ESymbol TeXSymbolType
_ Text
s -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s
ENumber Text
s -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s
EStyled TextType
sty [Exp]
xs -> [Text] -> Text
T.concat ([Text] -> Text) -> Maybe [Text] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Maybe Text] -> Maybe [Text]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ((Exp -> Maybe Text) -> [Exp] -> [Maybe Text]
forall a b. (a -> b) -> [a] -> [b]
map (TextType -> Exp -> Maybe Text
toStr TextType
sty) [Exp]
xs)
Exp
_ -> Maybe Text
forall a. Maybe a
Nothing
toStr :: TextType -> Exp -> Maybe Text
toStr TextType
sty (EIdentifier Text
s) = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
sty Text
s
toStr TextType
_ (EText TextType
sty' Text
s) = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
sty' Text
s
toStr TextType
sty (ENumber Text
s) = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
sty Text
s
toStr TextType
sty (EMathOperator Text
s) = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
sty Text
s
toStr TextType
sty (ESymbol TeXSymbolType
_ Text
s) = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Text
toUnicode TextType
sty Text
s
toStr TextType
_ (ESpace Rational
n) = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Rational -> Text
getSpaceChars Rational
n
toStr TextType
_ (EStyled TextType
sty' [Exp]
exps) = [Text] -> Text
T.concat ([Text] -> Text) -> Maybe [Text] -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
[Maybe Text] -> Maybe [Text]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ((Exp -> Maybe Text) -> [Exp] -> [Maybe Text]
forall a b. (a -> b) -> [a] -> [b]
map (TextType -> Exp -> Maybe Text
toStr TextType
sty') [Exp]
exps)
toStr TextType
_ Exp
_ = Maybe Text
forall a. Maybe a
Nothing
bareSubSup :: TP Exp
bareSubSup :: TP Exp
bareSubSup = Maybe Bool -> Bool -> Exp -> TP Exp
subSup Maybe Bool
forall a. Maybe a
Nothing Bool
False (Text -> Exp
EIdentifier Text
"")
TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Bool -> Bool -> Exp -> TP Exp
superOrSubscripted Maybe Bool
forall a. Maybe a
Nothing Bool
False (Text -> Exp
EIdentifier Text
"")
limitsIndicator :: TP (Maybe Bool)
limitsIndicator :: TP (Maybe Bool)
limitsIndicator =
(SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"limits" ParsecT Text () Identity SourceName
-> TP (Maybe Bool) -> TP (Maybe Bool)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe Bool -> TP (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True))
TP (Maybe Bool) -> TP (Maybe Bool) -> TP (Maybe Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"nolimits" ParsecT Text () Identity SourceName
-> TP (Maybe Bool) -> TP (Maybe Bool)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe Bool -> TP (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False))
TP (Maybe Bool) -> TP (Maybe Bool) -> TP (Maybe Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Bool -> TP (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Bool
forall a. Maybe a
Nothing
binomCmd :: TP Text
binomCmd :: TP Text
binomCmd = [Text] -> TP Text
oneOfCommands (Map Text (Exp -> Exp -> Exp) -> [Text]
forall k a. Map k a -> [k]
M.keys Map Text (Exp -> Exp -> Exp)
binomCmds)
binomCmds :: M.Map Text (Exp -> Exp -> Exp)
binomCmds :: Map Text (Exp -> Exp -> Exp)
binomCmds = [(Text, Exp -> Exp -> Exp)] -> Map Text (Exp -> Exp -> Exp)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"\\choose", \Exp
x Exp
y ->
Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
"(" Text
")" [Exp -> InEDelimited
forall a b. b -> Either a b
Right (FractionType -> Exp -> Exp -> Exp
EFraction FractionType
NoLineFrac Exp
x Exp
y)])
, (Text
"\\brack", \Exp
x Exp
y ->
Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
"[" Text
"]" [Exp -> InEDelimited
forall a b. b -> Either a b
Right (FractionType -> Exp -> Exp -> Exp
EFraction FractionType
NoLineFrac Exp
x Exp
y)])
, (Text
"\\brace", \Exp
x Exp
y ->
Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
"{" Text
"}" [Exp -> InEDelimited
forall a b. b -> Either a b
Right (FractionType -> Exp -> Exp -> Exp
EFraction FractionType
NoLineFrac Exp
x Exp
y)])
, (Text
"\\bangle", \Exp
x Exp
y ->
Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
"\x27E8" Text
"\x27E9" [Exp -> InEDelimited
forall a b. b -> Either a b
Right (FractionType -> Exp -> Exp -> Exp
EFraction FractionType
NoLineFrac Exp
x Exp
y)])
]
genfrac :: Text -> TP Exp
genfrac :: Text -> TP Exp
genfrac Text
"\\genfrac" = do
let opener :: ParsecT Text u Identity Text
opener = Text
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" (ParsecT Text u Identity Text -> ParsecT Text u Identity Text)
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall a b. (a -> b) -> a -> b
$
Char -> Text
T.singleton (Char -> Text)
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT Text u Identity Char
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar) ParsecT Text u Identity Char
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar)
let closer :: ParsecT Text u Identity Text
closer = Text
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" (ParsecT Text u Identity Text -> ParsecT Text u Identity Text)
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall a b. (a -> b) -> a -> b
$
Char -> Text
T.singleton (Char -> Text)
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT Text u Identity Char
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar) ParsecT Text u Identity Char
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar)
Text
openDelim <- TP Text -> TP Text
forall a. TP a -> TP a
braces TP Text
forall u. ParsecT Text u Identity Text
opener TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text
forall u. ParsecT Text u Identity Text
opener
Text
closeDelim <- TP Text -> TP Text
forall a. TP a -> TP a
braces TP Text
forall u. ParsecT Text u Identity Text
closer TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text
forall u. ParsecT Text u Identity Text
closer
Bool
bar <- Bool
False Bool
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a. TP a -> TP a
braces (SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"0pt")) ParsecT Text () Identity Bool
-> ParsecT Text () Identity Bool -> ParsecT Text () Identity Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool
True Bool -> TP Exp -> ParsecT Text () Identity Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ TP Exp
texToken
Bool
displayStyle <- Bool
True Bool
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a. TP a -> TP a
braces (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'0')) ParsecT Text () Identity Bool
-> ParsecT Text () Identity Bool -> ParsecT Text () Identity Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool
False Bool -> TP Exp -> ParsecT Text () Identity Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ TP Exp
texToken
Exp
x <- TP Exp
texToken
Exp
y <- TP Exp
texToken
let fracType :: FractionType
fracType = case (Bool
bar, Bool
displayStyle) of
(Bool
False, Bool
_) -> FractionType
NoLineFrac
(Bool
True, Bool
True) -> FractionType
DisplayFrac
(Bool, Bool)
_ -> FractionType
NormalFrac
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
openDelim Text
closeDelim
[Exp -> InEDelimited
forall a b. b -> Either a b
Right (FractionType -> Exp -> Exp -> Exp
EFraction FractionType
fracType Exp
x Exp
y)]
genfrac Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
substack :: Text -> TP Exp
substack :: Text -> TP Exp
substack Text
"\\substack" = do
[Exp]
formulas <- Parsec Text () [Exp] -> Parsec Text () [Exp]
forall a. TP a -> TP a
braces (Parsec Text () [Exp] -> Parsec Text () [Exp])
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity ()
ignorable ParsecT Text () Identity ()
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (TP Exp -> TP Exp
manyExp TP Exp
expr) TP Exp -> ParsecT Text () Identity Char -> Parsec Text () [Exp]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
`sepEndBy` ParsecT Text () Identity Char
endLine
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray [Alignment
AlignCenter] ([ArrayLine] -> Exp) -> [ArrayLine] -> Exp
forall a b. (a -> b) -> a -> b
$ (Exp -> ArrayLine) -> [Exp] -> [ArrayLine]
forall a b. (a -> b) -> [a] -> [b]
map (\Exp
x -> [[Exp
x]]) [Exp]
formulas
substack Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
asGroup :: [Exp] -> Exp
asGroup :: [Exp] -> Exp
asGroup [Exp
x] = Exp
x
asGroup [Exp]
xs = [Exp] -> Exp
EGrouped [Exp]
xs
manyExp' :: Bool -> TP Exp -> TP Exp
manyExp' :: Bool -> TP Exp -> TP Exp
manyExp' Bool
requireNonempty TP Exp
p = do
[Exp]
initial <- if Bool
requireNonempty
then TP Exp -> Parsec Text () [Exp]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (TP Text -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy TP Text
binomCmd ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TP Exp
p)
else TP Exp -> Parsec Text () [Exp]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (TP Text -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy TP Text
binomCmd ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TP Exp
p)
let withCmd :: Text -> TP Exp
withCmd :: Text -> TP Exp
withCmd Text
cmd =
case Text -> Map Text (Exp -> Exp -> Exp) -> Maybe (Exp -> Exp -> Exp)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
cmd Map Text (Exp -> Exp -> Exp)
binomCmds of
Just Exp -> Exp -> Exp
f -> Exp -> Exp -> Exp
f (Exp -> Exp -> Exp)
-> TP Exp -> ParsecT Text () Identity (Exp -> Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Exp] -> Exp
asGroup ([Exp] -> Exp) -> Parsec Text () [Exp] -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Exp] -> Parsec Text () [Exp]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Exp]
initial)
ParsecT Text () Identity (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([Exp] -> Exp
asGroup ([Exp] -> Exp) -> Parsec Text () [Exp] -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp -> Parsec Text () [Exp]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many TP Exp
p)
Maybe (Exp -> Exp -> Exp)
Nothing -> SourceName -> TP Exp
forall (m :: * -> *) a. MonadFail m => SourceName -> m a
fail (SourceName -> TP Exp) -> SourceName -> TP Exp
forall a b. (a -> b) -> a -> b
$ SourceName
"Unknown command " SourceName -> SourceName -> SourceName
forall a. Semigroup a => a -> a -> a
<> Text -> SourceName
T.unpack Text
cmd
(TP Text
binomCmd TP Text -> (Text -> TP Exp) -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> TP Exp
withCmd) TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return ([Exp] -> Exp
asGroup [Exp]
initial)
manyExp :: TP Exp -> TP Exp
manyExp :: TP Exp -> TP Exp
manyExp = Bool -> TP Exp -> TP Exp
manyExp' Bool
False
many1Exp :: TP Exp -> TP Exp
many1Exp :: TP Exp -> TP Exp
many1Exp = Bool -> TP Exp -> TP Exp
manyExp' Bool
True
inbraces :: TP Exp
inbraces :: TP Exp
inbraces = TP Exp -> TP Exp
forall a. TP a -> TP a
braces (TP Exp -> TP Exp
manyExp TP Exp
expr)
texToken :: TP Exp
texToken :: TP Exp
texToken = TP Exp
texSymbol TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
inbraces TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
texChar
deGroup :: Exp -> Exp
deGroup :: Exp -> Exp
deGroup (EGrouped [Exp
x]) = Exp
x
deGroup Exp
x = Exp
x
texChar :: TP Exp
texChar :: TP Exp
texChar =
do
Char
c <- SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
"\n\t\r \\{}" ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ (if Char -> Bool
isDigit Char
c then Text -> Exp
ENumber else Text -> Exp
EIdentifier) (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
c
inbrackets :: TP Exp
inbrackets :: TP Exp
inbrackets = (TP Exp -> TP Exp
forall a. TP a -> TP a
brackets (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ TP Exp -> TP Exp
manyExp (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']') ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TP Exp
expr)
number :: TP Exp
number :: TP Exp
number = TP Exp -> TP Exp
forall a. TP a -> TP a
lexeme (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Exp
ENumber (Text -> Exp) -> TP Text -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try TP Text
forall u. ParsecT Text u Identity Text
decimalNumber
where decimalNumber :: ParsecT Text u Identity Text
decimalNumber = do
SourceName
xs <- ParsecT Text u Identity Char -> ParsecT Text u Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Text u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit
SourceName
ys <- SourceName
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName)
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall a b. (a -> b) -> a -> b
$ ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.' ParsecT Text u Identity Char
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ((Char
'.'Char -> SourceName -> SourceName
forall a. a -> [a] -> [a]
:) (SourceName -> SourceName)
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text u Identity Char -> ParsecT Text u Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit))
case SourceName
xs SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ SourceName
ys of
[] -> ParsecT Text u Identity Text
forall (m :: * -> *) a. MonadPlus m => m a
mzero
SourceName
zs -> Text -> ParsecT Text u Identity Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Text u Identity Text)
-> Text -> ParsecT Text u Identity Text
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack SourceName
zs
enclosure :: TP Exp
enclosure :: TP Exp
enclosure = TP Exp
delimited TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
delimitedImplicit TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
basicEnclosure
basicEnclosure :: TP Exp
basicEnclosure :: TP Exp
basicEnclosure = TP Exp -> TP Exp
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
Text
possibleEncl <- TP Text -> TP Text
forall a. TP a -> TP a
lexeme (TP Text
anyCtrlSeq TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Line -> ParsecT Text () Identity Char -> TP Text
countChar Line
1 (SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"()[]|"))
case Text -> Map Text Exp -> Maybe Exp
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
possibleEncl Map Text Exp
enclosures of
Just Exp
x -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
x
Maybe Exp
Nothing -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
fence :: String -> TP Text
fence :: SourceName -> TP Text
fence SourceName
cmd = do
SourceName -> ParsecT Text () Identity SourceName
symbol SourceName
cmd
Exp
enc <- TP Exp
basicEnclosure TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT Text () Identity SourceName
symbol SourceName
".") ParsecT Text () Identity SourceName -> TP Exp -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
""))
case Exp
enc of
ESymbol TeXSymbolType
Open Text
x -> Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
x
ESymbol TeXSymbolType
Close Text
x -> Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
x
Exp
_ -> TP Text
forall (m :: * -> *) a. MonadPlus m => m a
mzero
middle :: TP Text
middle :: TP Text
middle = SourceName -> TP Text
fence SourceName
"\\middle"
right :: TP Text
right :: TP Text
right = SourceName -> TP Text
fence SourceName
"\\right"
delimited :: TP Exp
delimited :: TP Exp
delimited = do
Text
openc <- TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ SourceName -> TP Text
fence SourceName
"\\left"
[InEDelimited]
contents <- [[InEDelimited]] -> [InEDelimited]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[InEDelimited]] -> [InEDelimited])
-> ParsecT Text () Identity [[InEDelimited]]
-> ParsecT Text () Identity [InEDelimited]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [[InEDelimited]]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited])
-> ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
forall a b. (a -> b) -> a -> b
$ ((InEDelimited -> [InEDelimited] -> [InEDelimited]
forall a. a -> [a] -> [a]
:[]) (InEDelimited -> [InEDelimited])
-> (Text -> InEDelimited) -> Text -> [InEDelimited]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> InEDelimited
forall a b. a -> Either a b
Left (Text -> [InEDelimited])
-> TP Text -> ParsecT Text () Identity [InEDelimited]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Text
middle)
ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((Exp -> InEDelimited) -> [Exp] -> [InEDelimited]
forall a b. (a -> b) -> [a] -> [b]
map Exp -> InEDelimited
forall a b. b -> Either a b
Right ([Exp] -> [InEDelimited])
-> (Exp -> [Exp]) -> Exp -> [InEDelimited]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Exp -> [Exp]
unGrouped (Exp -> [InEDelimited])
-> TP Exp -> ParsecT Text () Identity [InEDelimited]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
TP Exp -> TP Exp
many1Exp (TP Text -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy TP Text
right ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP Exp
expr)))
Text
closec <- TP Text
right TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
openc Text
closec [InEDelimited]
contents
delimitedImplicit :: TP Exp
delimitedImplicit :: TP Exp
delimitedImplicit = TP Exp -> TP Exp
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
Char
openc <- ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a. TP a -> TP a
lexeme (ParsecT Text () Identity Char -> ParsecT Text () Identity Char)
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"()[]|"
Char
closec <- case Char
openc of
Char
'(' -> Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
')'
Char
'[' -> Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
']'
Char
'|' -> Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
'|'
Char
_ -> ParsecT Text () Identity Char
forall (m :: * -> *) a. MonadPlus m => m a
mzero
let closer :: ParsecT Text () Identity Char
closer = ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a. TP a -> TP a
lexeme (ParsecT Text () Identity Char -> ParsecT Text () Identity Char)
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
closec
[InEDelimited]
contents <- [[InEDelimited]] -> [InEDelimited]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[InEDelimited]] -> [InEDelimited])
-> ParsecT Text () Identity [[InEDelimited]]
-> ParsecT Text () Identity [InEDelimited]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [[InEDelimited]]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited])
-> ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
forall a b. (a -> b) -> a -> b
$ ((InEDelimited -> [InEDelimited] -> [InEDelimited]
forall a. a -> [a] -> [a]
:[]) (InEDelimited -> [InEDelimited])
-> (Text -> InEDelimited) -> Text -> [InEDelimited]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> InEDelimited
forall a b. a -> Either a b
Left (Text -> [InEDelimited])
-> TP Text -> ParsecT Text () Identity [InEDelimited]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Text
middle)
ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
-> ParsecT Text () Identity [InEDelimited]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((Exp -> InEDelimited) -> [Exp] -> [InEDelimited]
forall a b. (a -> b) -> [a] -> [b]
map Exp -> InEDelimited
forall a b. b -> Either a b
Right ([Exp] -> [InEDelimited])
-> (Exp -> [Exp]) -> Exp -> [InEDelimited]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Exp -> [Exp]
unGrouped (Exp -> [InEDelimited])
-> TP Exp -> ParsecT Text () Identity [InEDelimited]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
TP Exp -> TP Exp
many1Exp (ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Text () Identity Char
closer ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP Exp
expr)))
Char
_ <- ParsecT Text () Identity Char
closer
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [InEDelimited] -> Exp
EDelimited (Char -> Text
T.singleton Char
openc) (Char -> Text
T.singleton Char
closec) [InEDelimited]
contents
scaled :: Text -> TP Exp
scaled :: Text -> TP Exp
scaled Text
cmd = do
case Text -> Maybe Rational
S.getScalerValue Text
cmd of
Just Rational
r -> Rational -> Exp -> Exp
EScaled Rational
r (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TP Exp
basicEnclosure TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
operator)
Maybe Rational
Nothing -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
endLine :: TP Char
endLine :: ParsecT Text () Identity Char
endLine = ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity Char -> ParsecT Text () Identity Char)
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a b. (a -> b) -> a -> b
$ do
SourceName -> ParsecT Text () Identity SourceName
symbol SourceName
"\\\\"
TP Exp -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional TP Exp
inbrackets
Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
'\n'
endLineAMS :: TP Char
endLineAMS :: ParsecT Text () Identity Char
endLineAMS = ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a. TP a -> TP a
lexeme (ParsecT Text () Identity Char -> ParsecT Text () Identity Char)
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity Char -> ParsecT Text () Identity Char)
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a b. (a -> b) -> a -> b
$ do
SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\\\"
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Text () Identity ()
comment
TP Exp -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional TP Exp
inbrackets
Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
'\n'
arrayLine :: TP ArrayLine
arrayLine :: TP ArrayLine
arrayLine = ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"end" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
'\n') ParsecT Text () Identity () -> TP ArrayLine -> TP ArrayLine
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Parsec Text () [Exp]
-> ParsecT Text () Identity SourceName -> TP ArrayLine
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy1 (Exp -> [Exp]
unGrouped (Exp -> [Exp]) -> TP Exp -> Parsec Text () [Exp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
TP Exp -> TP Exp
manyExp (ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity ()
ignorable' ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Text () Identity Char
endLine) ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
TP Exp
expr TP Exp -> ParsecT Text () Identity () -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
ParsecT Text () Identity ()
ignorable')) (SourceName -> ParsecT Text () Identity SourceName
symbol SourceName
"&")
where ignorable' :: ParsecT Text () Identity ()
ignorable' = ParsecT Text () Identity ()
ignorable ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"hline" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text () Identity ()
ignorable'))
arrayAlignments :: TP [Alignment]
arrayAlignments :: TP [Alignment]
arrayAlignments = TP [Alignment] -> TP [Alignment]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP [Alignment] -> TP [Alignment])
-> TP [Alignment] -> TP [Alignment]
forall a b. (a -> b) -> a -> b
$ do
SourceName
as <- ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a. TP a -> TP a
braces (ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter ParsecT Text () Identity Char
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'|'))
let letterToAlignment :: Char -> Alignment
letterToAlignment Char
'l' = Alignment
AlignLeft
letterToAlignment Char
'c' = Alignment
AlignCenter
letterToAlignment Char
'r' = Alignment
AlignRight
letterToAlignment Char
_ = Alignment
AlignCenter
[Alignment] -> TP [Alignment]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Alignment] -> TP [Alignment]) -> [Alignment] -> TP [Alignment]
forall a b. (a -> b) -> a -> b
$ (Char -> Alignment) -> SourceName -> [Alignment]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Alignment
letterToAlignment (SourceName -> [Alignment]) -> SourceName -> [Alignment]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> SourceName -> SourceName
forall a. (a -> Bool) -> [a] -> [a]
filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'|') SourceName
as
environment :: Text -> TP Exp
environment :: Text -> TP Exp
environment Text
"\\begin" = do
Text
name <- TP Text -> TP Text
forall a. TP a -> TP a
braces ([Text] -> TP Text
oneOfStrings (Map Text (TP Exp) -> [Text]
forall k a. Map k a -> [k]
M.keys Map Text (TP Exp)
environments) TP Text -> ParsecT Text () Identity () -> TP Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'*'))
ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
case Text -> Map Text (TP Exp) -> Maybe (TP Exp)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
name Map Text (TP Exp)
environments of
Just TP Exp
env -> do
Exp
result <- TP Exp
env
ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"end"
TP Text -> TP Text
forall a. TP a -> TP a
braces (Text -> TP Text
textStr Text
name TP Text -> ParsecT Text () Identity () -> TP Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'*'))
ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
result
Maybe (TP Exp)
Nothing -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
environment Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
environments :: M.Map Text (TP Exp)
environments :: Map Text (TP Exp)
environments = [(Text, TP Exp)] -> Map Text (TP Exp)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"array", TP Exp
stdarray)
, (Text
"eqnarray", TP Exp
eqnarray)
, (Text
"align", TP Exp
align)
, (Text
"aligned", TP Exp
align)
, (Text
"alignat", TP Exp
inbraces TP Exp
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP Exp
align)
, (Text
"alignedat", TP Exp
inbraces TP Exp
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP Exp
align)
, (Text
"flalign", TP Exp
flalign)
, (Text
"flaligned", TP Exp
flalign)
, (Text
"cases", TP Exp
cases)
, (Text
"matrix", Text -> Text -> TP Exp
matrixWith Text
"" Text
"")
, (Text
"smallmatrix", Text -> Text -> TP Exp
matrixWith Text
"" Text
"")
, (Text
"pmatrix", Text -> Text -> TP Exp
matrixWith Text
"(" Text
")")
, (Text
"bmatrix", Text -> Text -> TP Exp
matrixWith Text
"[" Text
"]")
, (Text
"Bmatrix", Text -> Text -> TP Exp
matrixWith Text
"{" Text
"}")
, (Text
"vmatrix", Text -> Text -> TP Exp
matrixWith Text
"\x2223" Text
"\x2223")
, (Text
"Vmatrix", Text -> Text -> TP Exp
matrixWith Text
"\x2225" Text
"\x2225")
, (Text
"split", TP Exp
align)
, (Text
"multline", TP Exp
gather)
, (Text
"gather", TP Exp
gather)
, (Text
"gathered", TP Exp
gather)
, (Text
"equation", TP Exp
equation)
]
alignsFromRows :: Alignment -> [ArrayLine] -> [Alignment]
alignsFromRows :: Alignment -> [ArrayLine] -> [Alignment]
alignsFromRows Alignment
_ [] = []
alignsFromRows Alignment
defaultAlignment (ArrayLine
r:[ArrayLine]
_) = Line -> Alignment -> [Alignment]
forall a. Line -> a -> [a]
replicate (ArrayLine -> Line
forall (t :: * -> *) a. Foldable t => t a -> Line
length ArrayLine
r) Alignment
defaultAlignment
matrixWith :: Text -> Text -> TP Exp
matrixWith :: Text -> Text -> TP Exp
matrixWith Text
opendelim Text
closedelim = do
[ArrayLine]
lines' <- TP ArrayLine
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity [ArrayLine]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy1 TP ArrayLine
arrayLine ParsecT Text () Identity Char
endLineAMS
let aligns :: [Alignment]
aligns = Alignment -> [ArrayLine] -> [Alignment]
alignsFromRows Alignment
AlignCenter [ArrayLine]
lines'
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
opendelim Bool -> Bool -> Bool
&& Text -> Bool
T.null Text
closedelim
then [Alignment] -> [ArrayLine] -> Exp
EArray [Alignment]
aligns [ArrayLine]
lines'
else Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
opendelim Text
closedelim
[Exp -> InEDelimited
forall a b. b -> Either a b
Right (Exp -> InEDelimited) -> Exp -> InEDelimited
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray [Alignment]
aligns [ArrayLine]
lines']
stdarray :: TP Exp
stdarray :: TP Exp
stdarray = do
[Alignment]
aligns <- TP [Alignment]
arrayAlignments
[ArrayLine]
lines' <- TP ArrayLine
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity [ArrayLine]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy1 TP ArrayLine
arrayLine ParsecT Text () Identity Char
endLine
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray [Alignment]
aligns [ArrayLine]
lines'
gather :: TP Exp
gather :: TP Exp
gather = do
[ArrayLine]
rows <- TP ArrayLine
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity [ArrayLine]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy TP ArrayLine
arrayLine ParsecT Text () Identity Char
endLineAMS
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray (Alignment -> [ArrayLine] -> [Alignment]
alignsFromRows Alignment
AlignCenter [ArrayLine]
rows) [ArrayLine]
rows
equation :: TP Exp
equation :: TP Exp
equation = do
ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"end" ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
'\n')
TP Exp -> TP Exp
manyExp (ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Text () Identity Char
endLine ParsecT Text () Identity () -> TP Exp -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TP Exp
expr)
eqnarray :: TP Exp
eqnarray :: TP Exp
eqnarray = do
[ArrayLine]
rows <- TP ArrayLine
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity [ArrayLine]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy1 TP ArrayLine
arrayLine ParsecT Text () Identity Char
endLine
let n :: Line
n = [Line] -> Line
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Line] -> Line) -> [Line] -> Line
forall a b. (a -> b) -> a -> b
$ (ArrayLine -> Line) -> [ArrayLine] -> [Line]
forall a b. (a -> b) -> [a] -> [b]
map ArrayLine -> Line
forall (t :: * -> *) a. Foldable t => t a -> Line
length [ArrayLine]
rows
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray (Line -> [Alignment] -> [Alignment]
forall a. Line -> [a] -> [a]
take Line
n ([Alignment] -> [Alignment]) -> [Alignment] -> [Alignment]
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [Alignment]
forall a. [a] -> [a]
cycle [Alignment
AlignRight, Alignment
AlignCenter, Alignment
AlignLeft]) [ArrayLine]
rows
align :: TP Exp
align :: TP Exp
align = do
[ArrayLine]
rows <- TP ArrayLine
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity [ArrayLine]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy1 TP ArrayLine
arrayLine ParsecT Text () Identity Char
endLineAMS
let n :: Line
n = [Line] -> Line
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Line] -> Line) -> [Line] -> Line
forall a b. (a -> b) -> a -> b
$ (ArrayLine -> Line) -> [ArrayLine] -> [Line]
forall a b. (a -> b) -> [a] -> [b]
map ArrayLine -> Line
forall (t :: * -> *) a. Foldable t => t a -> Line
length [ArrayLine]
rows
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray (Line -> [Alignment] -> [Alignment]
forall a. Line -> [a] -> [a]
take Line
n ([Alignment] -> [Alignment]) -> [Alignment] -> [Alignment]
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [Alignment]
forall a. [a] -> [a]
cycle [Alignment
AlignRight, Alignment
AlignLeft]) [ArrayLine]
rows
flalign :: TP Exp
flalign :: TP Exp
flalign = do
[ArrayLine]
rows <- TP ArrayLine
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity [ArrayLine]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy1 TP ArrayLine
arrayLine ParsecT Text () Identity Char
endLineAMS
let n :: Line
n = [Line] -> Line
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Line] -> Line) -> [Line] -> Line
forall a b. (a -> b) -> a -> b
$ (ArrayLine -> Line) -> [ArrayLine] -> [Line]
forall a b. (a -> b) -> [a] -> [b]
map ArrayLine -> Line
forall (t :: * -> *) a. Foldable t => t a -> Line
length [ArrayLine]
rows
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray (Line -> [Alignment] -> [Alignment]
forall a. Line -> [a] -> [a]
take Line
n ([Alignment] -> [Alignment]) -> [Alignment] -> [Alignment]
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [Alignment]
forall a. [a] -> [a]
cycle [Alignment
AlignLeft, Alignment
AlignRight]) [ArrayLine]
rows
cases :: TP Exp
cases :: TP Exp
cases = do
[ArrayLine]
rs <- TP ArrayLine
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity [ArrayLine]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy1 TP ArrayLine
arrayLine ParsecT Text () Identity Char
endLineAMS
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
"{" Text
"" [Exp -> InEDelimited
forall a b. b -> Either a b
Right (Exp -> InEDelimited) -> Exp -> InEDelimited
forall a b. (a -> b) -> a -> b
$ [Alignment] -> [ArrayLine] -> Exp
EArray (Alignment -> [ArrayLine] -> [Alignment]
alignsFromRows Alignment
AlignLeft [ArrayLine]
rs) [ArrayLine]
rs]
variable :: TP Exp
variable :: TP Exp
variable = do
Char
v <- ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter
ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Exp
EIdentifier (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
v
isConvertible :: Exp -> Bool
isConvertible :: Exp -> Bool
isConvertible (EMathOperator Text
x) = Text
x Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
convertibleOps
where convertibleOps :: [Text]
convertibleOps = [ Text
"lim",Text
"liminf",Text
"limsup",Text
"inf",Text
"sup"
, Text
"min",Text
"max",Text
"Pr",Text
"det",Text
"gcd"
]
isConvertible (ESymbol TeXSymbolType
Rel Text
_) = Bool
True
isConvertible (ESymbol TeXSymbolType
Bin Text
_) = Bool
True
isConvertible (ESymbol TeXSymbolType
Op Text
x) = Text
x Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
convertibleSyms
where convertibleSyms :: [Text]
convertibleSyms = [Text
"\x2211",Text
"\x220F",Text
"\x22C2",
Text
"\x22C3",Text
"\x22C0",Text
"\x22C1",Text
"\x2A05",Text
"\x2A06",
Text
"\x2210",Text
"\x2A01",Text
"\x2A02",Text
"\x2A00",Text
"\x2A04"]
isConvertible Exp
_ = Bool
False
isUnderover :: Exp -> Bool
isUnderover :: Exp -> Bool
isUnderover (EOver Bool
_ Exp
_ (ESymbol TeXSymbolType
TOver Text
"\xFE37")) = Bool
True
isUnderover (EOver Bool
_ Exp
_ (ESymbol TeXSymbolType
TOver Text
"\x23B4")) = Bool
True
isUnderover (EOver Bool
_ Exp
_ (ESymbol TeXSymbolType
TOver Text
"\x23DE")) = Bool
True
isUnderover (EUnder Bool
_ Exp
_ (ESymbol TeXSymbolType
TUnder Text
"\xFE38")) = Bool
True
isUnderover (EUnder Bool
_ Exp
_ (ESymbol TeXSymbolType
TUnder Text
"\x23B5")) = Bool
True
isUnderover (EUnder Bool
_ Exp
_ (ESymbol TeXSymbolType
TUnder Text
"\x23DF")) = Bool
True
isUnderover Exp
_ = Bool
False
subSup :: Maybe Bool -> Bool -> Exp -> TP Exp
subSup :: Maybe Bool -> Bool -> Exp -> TP Exp
subSup Maybe Bool
limits Bool
convertible Exp
a = TP Exp -> TP Exp
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
let sub1 :: TP Exp
sub1 = SourceName -> ParsecT Text () Identity SourceName
symbol SourceName
"_" ParsecT Text () Identity SourceName -> TP Exp -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TP Exp
expr1
let sup1 :: TP Exp
sup1 = SourceName -> ParsecT Text () Identity SourceName
symbol SourceName
"^" ParsecT Text () Identity SourceName -> TP Exp -> TP Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TP Exp
expr1
(Exp
b,Exp
c) <- ParsecT Text () Identity (Exp, Exp)
-> ParsecT Text () Identity (Exp, Exp)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do {Exp
m <- TP Exp
sub1; Exp
n <- TP Exp
sup1; (Exp, Exp) -> ParsecT Text () Identity (Exp, Exp)
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp
m,Exp
n)})
ParsecT Text () Identity (Exp, Exp)
-> ParsecT Text () Identity (Exp, Exp)
-> ParsecT Text () Identity (Exp, Exp)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do {Exp
n <- TP Exp
sup1; Exp
m <- TP Exp
sub1; (Exp, Exp) -> ParsecT Text () Identity (Exp, Exp)
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp
m,Exp
n)})
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ case Maybe Bool
limits of
Just Bool
True -> Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
False Exp
a Exp
b Exp
c
Maybe Bool
Nothing | Bool
convertible Bool -> Bool -> Bool
|| Exp -> Bool
isConvertible Exp
a -> Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
True Exp
a Exp
b Exp
c
| Exp -> Bool
isUnderover Exp
a -> Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
False Exp
a Exp
b Exp
c
Maybe Bool
_ -> Exp -> Exp -> Exp -> Exp
ESubsup Exp
a Exp
b Exp
c
superOrSubscripted :: Maybe Bool -> Bool -> Exp -> TP Exp
superOrSubscripted :: Maybe Bool -> Bool -> Exp -> TP Exp
superOrSubscripted Maybe Bool
limits Bool
convertible Exp
a = TP Exp -> TP Exp
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
Char
c <- SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
"^_"
ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Exp
b <- TP Exp
expr
case Char
c of
Char
'^' -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ case Maybe Bool
limits of
Just Bool
True -> Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
a Exp
b
Maybe Bool
Nothing
| Bool
convertible Bool -> Bool -> Bool
|| Exp -> Bool
isConvertible Exp
a -> Bool -> Exp -> Exp -> Exp
EOver Bool
True Exp
a Exp
b
| Exp -> Bool
isUnderover Exp
a -> Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
a Exp
b
Maybe Bool
_ -> Exp -> Exp -> Exp
ESuper Exp
a Exp
b
Char
'_' -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ case Maybe Bool
limits of
Just Bool
True -> Bool -> Exp -> Exp -> Exp
EUnder Bool
False Exp
a Exp
b
Maybe Bool
Nothing
| Bool
convertible Bool -> Bool -> Bool
|| Exp -> Bool
isConvertible Exp
a -> Bool -> Exp -> Exp -> Exp
EUnder Bool
True Exp
a Exp
b
| Exp -> Bool
isUnderover Exp
a -> Bool -> Exp -> Exp -> Exp
EUnder Bool
False Exp
a Exp
b
Maybe Bool
_ -> Exp -> Exp -> Exp
ESub Exp
a Exp
b
Char
_ -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
unicode :: TP Exp
unicode :: TP Exp
unicode = TP Exp -> TP Exp
forall a. TP a -> TP a
lexeme (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$
do
Char
c <- (Char -> Bool) -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isAscii)
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (TeXSymbolType -> Text -> Exp
ESymbol (Char -> TeXSymbolType
getSymbolType Char
c) (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
c)
ensuremath :: Text -> TP Exp
ensuremath :: Text -> TP Exp
ensuremath Text
"\\ensuremath" = TP Exp
inbraces
ensuremath Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
styleOps :: M.Map Text ([Exp] -> Exp)
styleOps :: Map Text ([Exp] -> Exp)
styleOps = [(Text, [Exp] -> Exp)] -> Map Text ([Exp] -> Exp)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"\\mathrm", TextType -> [Exp] -> Exp
EStyled TextType
TextNormal)
, (Text
"\\mathup", TextType -> [Exp] -> Exp
EStyled TextType
TextNormal)
, (Text
"\\mathbf", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
, (Text
"\\boldsymbol", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
, (Text
"\\bm", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
, (Text
"\\symbf", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
, (Text
"\\mathbold", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
, (Text
"\\pmb", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
, (Text
"\\mathbfup", TextType -> [Exp] -> Exp
EStyled TextType
TextBold)
, (Text
"\\mathit", TextType -> [Exp] -> Exp
EStyled TextType
TextItalic)
, (Text
"\\mathtt", TextType -> [Exp] -> Exp
EStyled TextType
TextMonospace)
, (Text
"\\texttt", TextType -> [Exp] -> Exp
EStyled TextType
TextMonospace)
, (Text
"\\mathsf", TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerif)
, (Text
"\\mathsfup", TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerif)
, (Text
"\\mathbb", TextType -> [Exp] -> Exp
EStyled TextType
TextDoubleStruck)
, (Text
"\\mathds", TextType -> [Exp] -> Exp
EStyled TextType
TextDoubleStruck)
, (Text
"\\mathcal", TextType -> [Exp] -> Exp
EStyled TextType
TextScript)
, (Text
"\\mathscr", TextType -> [Exp] -> Exp
EStyled TextType
TextScript)
, (Text
"\\mathfrak", TextType -> [Exp] -> Exp
EStyled TextType
TextFraktur)
, (Text
"\\mathbfit", TextType -> [Exp] -> Exp
EStyled TextType
TextBoldItalic)
, (Text
"\\mathbfsfup", TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerifBold)
, (Text
"\\mathbfsfit", TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerifBoldItalic)
, (Text
"\\mathbfscr", TextType -> [Exp] -> Exp
EStyled TextType
TextBoldScript)
, (Text
"\\mathbffrak", TextType -> [Exp] -> Exp
EStyled TextType
TextBoldFraktur)
, (Text
"\\mathbfcal", TextType -> [Exp] -> Exp
EStyled TextType
TextBoldScript)
, (Text
"\\mathsfit", TextType -> [Exp] -> Exp
EStyled TextType
TextSansSerifItalic)
]
phantom :: Text -> TP Exp
phantom :: Text -> TP Exp
phantom Text
"\\phantom" = Exp -> Exp
EPhantom (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken
phantom Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
boxed :: Text -> TP Exp
boxed :: Text -> TP Exp
boxed Text
"\\boxed" = Exp -> Exp
EBoxed (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken
boxed Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
text :: Text -> TP Exp
text :: Text -> TP Exp
text Text
c = do
Text -> Exp
op <- ParsecT Text () Identity (Text -> Exp)
-> ((Text -> Exp) -> ParsecT Text () Identity (Text -> Exp))
-> Maybe (Text -> Exp)
-> ParsecT Text () Identity (Text -> Exp)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ParsecT Text () Identity (Text -> Exp)
forall (m :: * -> *) a. MonadPlus m => m a
mzero (Text -> Exp) -> ParsecT Text () Identity (Text -> Exp)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Text -> Exp) -> ParsecT Text () Identity (Text -> Exp))
-> Maybe (Text -> Exp) -> ParsecT Text () Identity (Text -> Exp)
forall a b. (a -> b) -> a -> b
$ Text -> Map Text (Text -> Exp) -> Maybe (Text -> Exp)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
c Map Text (Text -> Exp)
textOps
Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{'
let chunk :: TP Exp
chunk = ((Text -> Exp
op (Text -> Exp) -> ([Text] -> Text) -> [Text] -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat) ([Text] -> Exp) -> ParsecT Text () Identity [Text] -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Text -> ParsecT Text () Identity [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 TP Text
textual)
TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{' ParsecT Text () Identity Char -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ([Exp] -> Exp
asGroup ([Exp] -> Exp) -> Parsec Text () [Exp] -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp -> ParsecT Text () Identity Char -> Parsec Text () [Exp]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill TP Exp
chunk (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}')))
TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
innermath
[Exp]
contents <- TP Exp -> ParsecT Text () Identity Char -> Parsec Text () [Exp]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill TP Exp
chunk (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}')
ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
case [Exp]
contents of
[] -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Exp
op Text
"")
[Exp
x] -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
x
[Exp]
xs -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return ([Exp] -> Exp
EGrouped [Exp]
xs)
innermath :: TP Exp
innermath :: TP Exp
innermath = [TP Exp] -> TP Exp
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([TP Exp] -> TP Exp) -> [TP Exp] -> TP Exp
forall a b. (a -> b) -> a -> b
$ ((SourceName, SourceName) -> TP Exp)
-> [(SourceName, SourceName)] -> [TP Exp]
forall a b. (a -> b) -> [a] -> [b]
map (SourceName, SourceName) -> TP Exp
innerMathWith
[(SourceName
"$",SourceName
"$"),(SourceName
"$$",SourceName
"$$"),(SourceName
"\\(",SourceName
"\\)"),(SourceName
"\\[",SourceName
"\\]")]
innerMathWith :: (String, String) -> TP Exp
innerMathWith :: (SourceName, SourceName) -> TP Exp
innerMathWith (SourceName
opener, SourceName
closer) = do
ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
opener)
Exp
e <- TP Exp -> TP Exp
manyExp TP Exp
expr
SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
closer
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
e
textOps :: M.Map Text (Text -> Exp)
textOps :: Map Text (Text -> Exp)
textOps = [(Text, Text -> Exp)] -> Map Text (Text -> Exp)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"\\textrm", (TextType -> Text -> Exp
EText TextType
TextNormal))
, (Text
"\\text", (TextType -> Text -> Exp
EText TextType
TextNormal))
, (Text
"\\textbf", (TextType -> Text -> Exp
EText TextType
TextBold))
, (Text
"\\textit", (TextType -> Text -> Exp
EText TextType
TextItalic))
, (Text
"\\texttt", (TextType -> Text -> Exp
EText TextType
TextMonospace))
, (Text
"\\textsf", (TextType -> Text -> Exp
EText TextType
TextSansSerif))
, (Text
"\\mbox", (TextType -> Text -> Exp
EText TextType
TextNormal))
]
styled :: Text -> TP Exp
styled :: Text -> TP Exp
styled Text
c = do
case Text -> Map Text ([Exp] -> Exp) -> Maybe ([Exp] -> Exp)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
c Map Text ([Exp] -> Exp)
styleOps of
Just [Exp] -> Exp
f -> do
Exp
x <- TP Exp
texSymbol TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
inbraces TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
texChar
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ case Exp
x of
EGrouped [Exp]
xs -> [Exp] -> Exp
f [Exp]
xs
Exp
_ -> [Exp] -> Exp
f [Exp
x]
Maybe ([Exp] -> Exp)
Nothing -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
root :: Text -> TP Exp
root :: Text -> TP Exp
root Text
c = do
Bool -> ParsecT Text () Identity ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Text () Identity ())
-> Bool -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ Text
c Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\\sqrt" Bool -> Bool -> Bool
|| Text
c Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\\surd"
(Exp -> Exp -> Exp
ERoot (Exp -> Exp -> Exp)
-> TP Exp -> ParsecT Text () Identity (Exp -> Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
inbrackets ParsecT Text () Identity (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TP Exp
texToken) TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Exp -> Exp
ESqrt (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken)
xspace :: Text -> TP Exp
xspace :: Text -> TP Exp
xspace Text
"\\mspace" = do
SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"mspace"
TP Exp -> TP Exp
forall a. TP a -> TP a
braces (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
SourceName
len <- ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit
ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a. TP a -> TP a
lexeme (ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName)
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"mu"
case ReadS Integer
forall a. Read a => ReadS a
reads SourceName
len of
((Integer
n :: Integer,[]):[(Integer, SourceName)]
_) -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Rational -> Exp
ESpace (Integer -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
nRational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18)
[(Integer, SourceName)]
_ -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
xspace Text
"\\hspace" = do
TP Exp -> TP Exp
forall a. TP a -> TP a
braces (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
SourceName
len <- ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit
Rational
scaleFactor <-
Rational
1 Rational
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Rational
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"em")
ParsecT Text () Identity Rational
-> ParsecT Text () Identity Rational
-> ParsecT Text () Identity Rational
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Rational
1Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
12) Rational
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Rational
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"pt")
ParsecT Text () Identity Rational
-> ParsecT Text () Identity Rational
-> ParsecT Text () Identity Rational
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Rational
6 Rational
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Rational
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"in")
ParsecT Text () Identity Rational
-> ParsecT Text () Identity Rational
-> ParsecT Text () Identity Rational
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Rational
50Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
21) Rational
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity Rational
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"cm")
case ReadS Integer
forall a. Read a => ReadS a
reads SourceName
len of
((Integer
n :: Integer,[]):[(Integer, SourceName)]
_) -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Rational -> Exp
ESpace (Integer -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
scaleFactor)
[(Integer, SourceName)]
_ -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
xspace Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
mathop :: Text -> TP Exp
mathop :: Text -> TP Exp
mathop Text
c =
case Text
c of
Text
"\\mathop" -> TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
Op
Text
"\\mathrel" -> TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
Rel
Text
"\\mathbin" -> TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
Bin
Text
"\\mathord" -> TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
Ord
Text
"\\mathopen" -> TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
Open
Text
"\\mathclose" -> TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
Close
Text
"\\mathpunct" -> TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
Pun
Text
_ -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
mathopWith :: TeXSymbolType -> TP Exp
mathopWith :: TeXSymbolType -> TP Exp
mathopWith TeXSymbolType
ty = do
Exp
e <- TP Exp
inbraces TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
expr1
let es' :: [Exp]
es' = case Exp
e of
EGrouped [Exp]
xs -> [Exp]
xs
Exp
x -> [Exp
x]
case [Exp]
es' of
[ESymbol TeXSymbolType
_ Text
x] -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
ty Text
x
[EIdentifier Text
x] -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
ty Text
x
[EText TextType
TextNormal Text
x] -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
ty Text
x
[EText TextType
sty Text
x] -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ TextType -> [Exp] -> Exp
EStyled TextType
sty [TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
ty Text
x]
[Exp]
xs | TeXSymbolType
ty TeXSymbolType -> TeXSymbolType -> Bool
forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Op -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Exp
EMathOperator (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$
[Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Exp -> Maybe Text) -> [Exp] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Exp -> Maybe Text
expToOperatorName [Exp]
xs
| Bool
otherwise -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped [Exp]
xs
binary :: Text -> TP Exp
binary :: Text -> TP Exp
binary Text
c = do
case Text
c of
Text
"\\overset" -> do
Exp
a <- TP Exp
texToken
Exp
b <- TP Exp
texToken
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
b Exp
a
Text
"\\stackrel" -> do
Exp
a <- TP Exp
texToken
Exp
b <- TP Exp
texToken
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
b Exp
a
Text
"\\underset" -> do
Exp
a <- TP Exp
texToken
Exp
b <- TP Exp
texToken
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Bool -> Exp -> Exp -> Exp
EUnder Bool
False Exp
b Exp
a
Text
"\\frac" -> FractionType -> Exp -> Exp -> Exp
EFraction FractionType
NormalFrac (Exp -> Exp -> Exp)
-> TP Exp -> ParsecT Text () Identity (Exp -> Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken ParsecT Text () Identity (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TP Exp
texToken
Text
"\\tfrac" -> FractionType -> Exp -> Exp -> Exp
EFraction FractionType
InlineFrac (Exp -> Exp -> Exp)
-> TP Exp -> ParsecT Text () Identity (Exp -> Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken ParsecT Text () Identity (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TP Exp
texToken
Text
"\\dfrac" -> FractionType -> Exp -> Exp -> Exp
EFraction FractionType
DisplayFrac (Exp -> Exp -> Exp)
-> TP Exp -> ParsecT Text () Identity (Exp -> Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken ParsecT Text () Identity (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TP Exp
texToken
Text
"\\binom" -> do
Exp
a <- TP Exp
texToken
Exp
b <- TP Exp
texToken
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
"(" Text
")" [Exp -> InEDelimited
forall a b. b -> Either a b
Right (FractionType -> Exp -> Exp -> Exp
EFraction FractionType
NoLineFrac Exp
a Exp
b)]
Text
_ -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
texSymbol :: TP Exp
texSymbol :: TP Exp
texSymbol = TP Exp
operator TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
TP Exp -> TP Exp
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do Text
c <- TP Text
anyCtrlSeq
Text -> TP Exp
tSymbol Text
c TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> TP Exp
negated Text
c)
negated :: Text -> TP Exp
negated :: Text -> TP Exp
negated Text
"\\not" = do
Exp
sym <- TP Exp
texSymbol TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
texChar
case Exp
sym of
ESymbol TeXSymbolType
Rel Text
x -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text
toNeg Text
x
EText TextType
tt Text
x -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ TextType -> Text -> Exp
EText TextType
tt (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text
toNeg Text
x
ENumber Text
x -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Exp
ENumber (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text
toNeg Text
x
EIdentifier Text
x -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Text -> Exp
EIdentifier (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Text -> Text
toNeg Text
x
Exp
_ -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
negated Text
_ = TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
toNeg :: Text -> Text
toNeg :: Text -> Text
toNeg Text
x = case Text
x of
Text
"\x2203" -> Text
"\x2204"
Text
"\x2208" -> Text
"\x2209"
Text
"\x220B" -> Text
"\x220C"
Text
"\x2223" -> Text
"\x2224"
Text
"\x2225" -> Text
"\x2226"
Text
"\x2243" -> Text
"\x2244"
Text
"\x2245" -> Text
"\x2246"
Text
"\x2248" -> Text
"\x2249"
Text
"=" -> Text
"\x2260"
Text
"\x2261" -> Text
"\x2262"
Text
"<" -> Text
"\x226E"
Text
">" -> Text
"\x226F"
Text
"\x2264" -> Text
"\x2270"
Text
"\x2265" -> Text
"\x2271"
Text
"\x2272" -> Text
"\x2274"
Text
"\x2273" -> Text
"\x2275"
Text
"\x227A" -> Text
"\x2280"
Text
"\x227B" -> Text
"\x2281"
Text
"\x2282" -> Text
"\x2284"
Text
"\x2283" -> Text
"\x2285"
Text
"\x2286" -> Text
"\x2288"
Text
"\x2287" -> Text
"\x2289"
Text
"\x227C" -> Text
"\x22E0"
Text
"\x227D" -> Text
"\x22E1"
Text
"\x2291" -> Text
"\x22E2"
Text
"\x2292" -> Text
"\x22E3"
Text
_ -> Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\x0338"
oneOfCommands :: [Text] -> TP Text
oneOfCommands :: [Text] -> TP Text
oneOfCommands [Text]
cmds = TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ do
Text
cmd <- [Text] -> TP Text
oneOfStrings [Text]
cmds
case Text -> SourceName
T.unpack Text
cmd of
[Char
'\\',Char
c] | Bool -> Bool
not (Char -> Bool
isLetter Char
c) -> () -> ParsecT Text () Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
SourceName
cmd' -> (do SourcePos
pos <- ParsecT Text () Identity SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter
SourcePos -> ParsecT Text () Identity ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
pos
ParsecT Text () Identity ()
forall (m :: * -> *) a. MonadPlus m => m a
mzero ParsecT Text () Identity ()
-> SourceName -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> SourceName -> ParsecT s u m a
<?> (SourceName
"non-letter after " SourceName -> SourceName -> SourceName
forall a. Semigroup a => a -> a -> a
<> SourceName
cmd'))
ParsecT Text () Identity ()
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () -> ParsecT Text () Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
cmd
oneOfStrings' :: (Char -> Char -> Bool) -> [(String, Text)] -> TP Text
oneOfStrings' :: (Char -> Char -> Bool) -> [(SourceName, Text)] -> TP Text
oneOfStrings' Char -> Char -> Bool
_ [] = TP Text
forall (m :: * -> *) a. MonadPlus m => m a
mzero
oneOfStrings' Char -> Char -> Bool
matches [(SourceName, Text)]
strs = TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ do
Char
c <- ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar
let strs' :: [(SourceName, Text)]
strs' = [(SourceName
xs, Text
t) | ((Char
x:SourceName
xs), Text
t) <- [(SourceName, Text)]
strs, Char
x Char -> Char -> Bool
`matches` Char
c]
case [(SourceName, Text)]
strs' of
[] -> TP Text
forall (m :: * -> *) a. MonadPlus m => m a
mzero
[(SourceName, Text)]
_ -> (Char -> Char -> Bool) -> [(SourceName, Text)] -> TP Text
oneOfStrings' Char -> Char -> Bool
matches [(SourceName, Text)]
strs'
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> case ((SourceName, Text) -> Bool)
-> [(SourceName, Text)] -> Maybe (SourceName, Text)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (SourceName -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SourceName -> Bool)
-> ((SourceName, Text) -> SourceName) -> (SourceName, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceName, Text) -> SourceName
forall a b. (a, b) -> a
fst) [(SourceName, Text)]
strs' of
Just (SourceName
_, Text
t) -> Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
t
Maybe (SourceName, Text)
Nothing -> TP Text
forall (m :: * -> *) a. MonadPlus m => m a
mzero
oneOfStrings :: [Text] -> TP Text
oneOfStrings :: [Text] -> TP Text
oneOfStrings [Text]
strs = (Char -> Char -> Bool) -> [(SourceName, Text)] -> TP Text
oneOfStrings' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
(==) [(SourceName, Text)]
strs' TP Text -> SourceName -> TP Text
forall (m :: * -> *) s u a.
Monad m =>
ParsecT s u m a -> SourceName -> ParsecT s u m a
<??> (SourceName -> [SourceName] -> SourceName
forall a. [a] -> [[a]] -> [a]
intercalate SourceName
", " ([SourceName] -> SourceName) -> [SourceName] -> SourceName
forall a b. (a -> b) -> a -> b
$ (Text -> SourceName) -> [Text] -> [SourceName]
forall a b. (a -> b) -> [a] -> [b]
map Text -> SourceName
forall a. Show a => a -> SourceName
show [Text]
strs)
where
strs' :: [(SourceName, Text)]
strs' = (Text -> (SourceName, Text)) -> [Text] -> [(SourceName, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (\Text
x -> (Text -> SourceName
T.unpack Text
x, Text
x)) [Text]
strs
(<??>) :: Monad m => ParsecT s u m a -> String -> ParsecT s u m a
<??> :: ParsecT s u m a -> SourceName -> ParsecT s u m a
(<??>) ParsecT s u m a
p SourceName
expected = do
SourcePos
pos <- ParsecT s u m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
ParsecT s u m a
p ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (SourcePos -> ParsecT s u m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
pos ParsecT s u m () -> ParsecT s u m a -> ParsecT s u m a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT s u m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero ParsecT s u m a -> SourceName -> ParsecT s u m a
forall s u (m :: * -> *) a.
ParsecT s u m a -> SourceName -> ParsecT s u m a
<?> SourceName
expected)
infix 0 <??>
tSymbol :: Text -> TP Exp
tSymbol :: Text -> TP Exp
tSymbol Text
sym =
case Text -> Map Text Exp -> Maybe Exp
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
sym Map Text Exp
symbols of
Just acc :: Exp
acc@(ESymbol TeXSymbolType
Accent Text
_) ->
(\Exp
t -> Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
t Exp
acc) (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken
Just acc :: Exp
acc@(ESymbol TeXSymbolType
TUnder Text
_) ->
(\Exp
t -> Bool -> Exp -> Exp -> Exp
EUnder Bool
False Exp
t Exp
acc) (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken
Just acc :: Exp
acc@(ESymbol TeXSymbolType
TOver Text
_) ->
(\Exp
t -> Bool -> Exp -> Exp -> Exp
EOver Bool
False Exp
t Exp
acc) (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
texToken
Just Exp
x -> Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
x
Maybe Exp
Nothing
| Text
sym Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\\mod" -> do
Exp
x <- Exp -> Exp
deGroup (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
expr
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped
[Rational -> Exp
ESpace (Rational
8Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18), Text -> Exp
EMathOperator Text
"mod", Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18), Exp
x]
| Text
sym Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\\bmod" -> do
Exp
x <- Exp -> Exp
deGroup (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
expr
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped
[Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18), Text -> Exp
EMathOperator Text
"mod", Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18), Exp
x]
| Text
sym Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\\pmod" -> do
Exp
x <- Exp -> Exp
deGroup (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
expr
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped
[Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18), TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"(", Text -> Exp
EMathOperator Text
"mod",
Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18), Exp
x, TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
")"]
| Text
sym Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\\pod" -> do
Exp
x <- Exp -> Exp
deGroup (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
expr
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped
[Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18), TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"(", Exp
x, TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
")"]
| Bool
otherwise -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
operator :: TP Exp
operator :: TP Exp
operator = do
Text
sym <- TP Text -> TP Text
forall a. TP a -> TP a
lexeme ([Text] -> TP Text
oneOfStrings ([Text] -> TP Text) -> [Text] -> TP Text
forall a b. (a -> b) -> a -> b
$ Map Text Exp -> [Text]
forall k a. Map k a -> [k]
M.keys Map Text Exp
operators)
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Maybe Exp -> Exp
forall a. HasCallStack => Maybe a -> a
fromJust (Text -> Map Text Exp -> Maybe Exp
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
sym Map Text Exp
operators)
lexeme :: TP a -> TP a
lexeme :: TP a -> TP a
lexeme TP a
p = TP a
p TP a -> ParsecT Text () Identity () -> TP a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
ignorable
braces :: TP a -> TP a
braces :: TP a -> TP a
braces TP a
p = TP a -> TP a
forall a. TP a -> TP a
lexeme (TP a -> TP a) -> TP a -> TP a
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity () -> TP a -> TP a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP a
p TP a -> ParsecT Text () Identity () -> TP a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces TP a -> ParsecT Text () Identity Char -> TP a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}'
brackets :: TP a -> TP a
brackets :: TP a -> TP a
brackets TP a
p = TP a -> TP a
forall a. TP a -> TP a
lexeme (TP a -> TP a) -> TP a -> TP a
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'[' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity () -> TP a -> TP a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP a
p TP a -> ParsecT Text () Identity () -> TP a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces TP a -> ParsecT Text () Identity Char -> TP a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']'
textStr :: Text -> TP Text
textStr :: Text -> TP Text
textStr Text
t = SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string (Text -> SourceName
T.unpack Text
t) ParsecT Text () Identity SourceName -> Text -> TP Text
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Text
t
countChar :: Int -> TP Char -> TP Text
countChar :: Line -> ParsecT Text () Identity Char -> TP Text
countChar Line
n = (SourceName -> Text)
-> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SourceName -> Text
T.pack (ParsecT Text () Identity SourceName -> TP Text)
-> (ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName)
-> ParsecT Text () Identity Char
-> TP Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Line
-> ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
Line -> ParsecT s u m a -> ParsecT s u m [a]
count Line
n
symbol :: String -> TP String
symbol :: SourceName -> ParsecT Text () Identity SourceName
symbol SourceName
s = ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a. TP a -> TP a
lexeme (ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName)
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName)
-> ParsecT Text () Identity SourceName
-> ParsecT Text () Identity SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
s
enclosures :: M.Map Text Exp
enclosures :: Map Text Exp
enclosures = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"(", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"(")
, (Text
")", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
")")
, (Text
"[", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"[")
, (Text
"]", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"]")
, (Text
"\\{", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"{")
, (Text
"\\}", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"}")
, (Text
"\\lbrack", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"[")
, (Text
"\\lbrace", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"{")
, (Text
"\\rbrack", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"]")
, (Text
"\\rbrace", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"}")
, (Text
"\\llbracket", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x27E6")
, (Text
"\\rrbracket", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x27E7")
, (Text
"\\langle", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x27E8")
, (Text
"\\rangle", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x27E9")
, (Text
"\\lfloor", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x230A")
, (Text
"\\rfloor", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x230B")
, (Text
"\\lceil", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x2308")
, (Text
"\\rceil", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2309")
, (Text
"|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"|")
, (Text
"|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"|")
, (Text
"\\|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x2225")
, (Text
"\\|", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2225")
, (Text
"\\lvert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x7C")
, (Text
"\\rvert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x7C")
, (Text
"\\vert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x7C")
, (Text
"\\lVert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x2225")
, (Text
"\\rVert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2225")
, (Text
"\\Vert", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x2016")
, (Text
"\\ulcorner", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\x231C")
, (Text
"\\urcorner", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\x231D")
]
operators :: M.Map Text Exp
operators :: Map Text Exp
operators = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [
(Text
"+", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"+")
, (Text
"-", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\x2212")
, (Text
"*", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"*")
, (Text
"@", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"@")
, (Text
",", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
",")
, (Text
".", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
".")
, (Text
";", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
";")
, (Text
":", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
":")
, (Text
"?", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"?")
, (Text
">", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
">")
, (Text
"<", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"<")
, (Text
"!", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"!")
, (Text
"'", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2032")
, (Text
"''", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2033")
, (Text
"'''", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2034")
, (Text
"''''", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\x2057")
, (Text
"=", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"=")
, (Text
":=", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
":=")
, (Text
"/", TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"/")
, (Text
"~", Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18)) ]
symbols :: M.Map Text Exp
symbols :: Map Text Exp
symbols = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"\\$",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"$")
, (Text
"\\%",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"%")
, (Text
"\\&",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"&")
, (Text
"\\_",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"_")
, (Text
"\\#",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"#")
, (Text
"\\^",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"^")
, (Text
"\\mid",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8739")
, (Text
"\\colon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
":")
, (Text
"\\parallel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8741")
, (Text
"\\backslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8726")
, (Text
"\\setminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\\")
, (Text
"\\times",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\215")
, (Text
"\\ltimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8905")
, (Text
"\\rtimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8906")
, (Text
"\\alpha",Text -> Exp
EIdentifier Text
"\945")
, (Text
"\\beta",Text -> Exp
EIdentifier Text
"\946")
, (Text
"\\chi",Text -> Exp
EIdentifier Text
"\967")
, (Text
"\\delta",Text -> Exp
EIdentifier Text
"\948")
, (Text
"\\Delta",Text -> Exp
EIdentifier Text
"\916")
, (Text
"\\epsilon",Text -> Exp
EIdentifier Text
"\1013")
, (Text
"\\varepsilon",Text -> Exp
EIdentifier Text
"\949")
, (Text
"\\eta",Text -> Exp
EIdentifier Text
"\951")
, (Text
"\\gamma",Text -> Exp
EIdentifier Text
"\947")
, (Text
"\\Gamma",Text -> Exp
EIdentifier Text
"\915")
, (Text
"\\iota",Text -> Exp
EIdentifier Text
"\953")
, (Text
"\\kappa",Text -> Exp
EIdentifier Text
"\954")
, (Text
"\\lambda",Text -> Exp
EIdentifier Text
"\955")
, (Text
"\\Lambda",Text -> Exp
EIdentifier Text
"\923")
, (Text
"\\mu",Text -> Exp
EIdentifier Text
"\956")
, (Text
"\\nu",Text -> Exp
EIdentifier Text
"\957")
, (Text
"\\omega",Text -> Exp
EIdentifier Text
"\969")
, (Text
"\\Omega",Text -> Exp
EIdentifier Text
"\937")
, (Text
"\\phi",Text -> Exp
EIdentifier Text
"\981")
, (Text
"\\varphi",Text -> Exp
EIdentifier Text
"\966")
, (Text
"\\Phi",Text -> Exp
EIdentifier Text
"\934")
, (Text
"\\pi",Text -> Exp
EIdentifier Text
"\960")
, (Text
"\\Pi",Text -> Exp
EIdentifier Text
"\928")
, (Text
"\\psi",Text -> Exp
EIdentifier Text
"\968")
, (Text
"\\Psi",Text -> Exp
EIdentifier Text
"\936")
, (Text
"\\rho",Text -> Exp
EIdentifier Text
"\961")
, (Text
"\\sigma",Text -> Exp
EIdentifier Text
"\963")
, (Text
"\\Sigma",Text -> Exp
EIdentifier Text
"\931")
, (Text
"\\tau",Text -> Exp
EIdentifier Text
"\964")
, (Text
"\\theta",Text -> Exp
EIdentifier Text
"\952")
, (Text
"\\vartheta",Text -> Exp
EIdentifier Text
"\977")
, (Text
"\\Theta",Text -> Exp
EIdentifier Text
"\920")
, (Text
"\\upsilon",Text -> Exp
EIdentifier Text
"\965")
, (Text
"\\Upsilon",Text -> Exp
EIdentifier Text
"\933")
, (Text
"\\xi",Text -> Exp
EIdentifier Text
"\958")
, (Text
"\\Xi",Text -> Exp
EIdentifier Text
"\926")
, (Text
"\\zeta",Text -> Exp
EIdentifier Text
"\950")
, (Text
"\\pm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\177")
, (Text
"\\mp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8723")
, (Text
"\\triangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8882")
, (Text
"\\triangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8883")
, (Text
"\\cdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8901")
, (Text
"\\star",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8902")
, (Text
"\\ast",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"*")
, (Text
"\\times",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\215")
, (Text
"\\div",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\247")
, (Text
"\\circ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8728")
, (Text
"\\bullet",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8226")
, (Text
"\\oplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8853")
, (Text
"\\ominus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8854")
, (Text
"\\otimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8855")
, (Text
"\\bigcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9675")
, (Text
"\\oslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8856")
, (Text
"\\odot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8857")
, (Text
"\\land",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8743")
, (Text
"\\wedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8743")
, (Text
"\\lor",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8744")
, (Text
"\\vee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8744")
, (Text
"\\cap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8745")
, (Text
"\\cup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8746")
, (Text
"\\sqcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8851")
, (Text
"\\sqcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8852")
, (Text
"\\uplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8846")
, (Text
"\\amalg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8720")
, (Text
"\\bigtriangleup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9651")
, (Text
"\\bigtriangledown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9661")
, (Text
"\\dag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8224")
, (Text
"\\dagger",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8224")
, (Text
"\\ddag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8225")
, (Text
"\\ddagger",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8225")
, (Text
"\\lhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8882")
, (Text
"\\rhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8883")
, (Text
"\\unlhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8884")
, (Text
"\\unrhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8885")
, (Text
"\\lt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"<")
, (Text
"\\gt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
">")
, (Text
"\\ne",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8800")
, (Text
"\\neq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8800")
, (Text
"\\le",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8804")
, (Text
"\\leq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8804")
, (Text
"\\leqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8804")
, (Text
"\\ge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8805")
, (Text
"\\geq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8805")
, (Text
"\\geqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8805")
, (Text
"\\equiv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8801")
, (Text
"\\ll",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8810")
, (Text
"\\gg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8811")
, (Text
"\\doteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8784")
, (Text
"\\prec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8826")
, (Text
"\\succ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8827")
, (Text
"\\preceq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8828")
, (Text
"\\succeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8829")
, (Text
"\\subset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8834")
, (Text
"\\supset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8835")
, (Text
"\\subseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8838")
, (Text
"\\supseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8839")
, (Text
"\\nsubset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8836")
, (Text
"\\nsupset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8837")
, (Text
"\\nsubseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8840")
, (Text
"\\nsupseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8841")
, (Text
"\\sqsubset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8847")
, (Text
"\\sqsupset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8848")
, (Text
"\\sqsubseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8849")
, (Text
"\\sqsupseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8850")
, (Text
"\\sim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8764")
, (Text
"\\simeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8771")
, (Text
"\\approx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8776")
, (Text
"\\cong",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8773")
, (Text
"\\Join",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8904")
, (Text
"\\bowtie",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8904")
, (Text
"\\in",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8712")
, (Text
"\\ni",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8715")
, (Text
"\\owns",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8715")
, (Text
"\\propto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8733")
, (Text
"\\vdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8866")
, (Text
"\\dashv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8867")
, (Text
"\\models",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8872")
, (Text
"\\perp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8869")
, (Text
"\\smile",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8995")
, (Text
"\\frown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8994")
, (Text
"\\asymp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8781")
, (Text
"\\notin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8713")
, (Text
"\\gets",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8592")
, (Text
"\\leftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8592")
, (Text
"\\nwarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8598")
, (Text
"\\nearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8599")
, (Text
"\\searrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8600")
, (Text
"\\swarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8601")
, (Text
"\\to",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8594")
, (Text
"\\rightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8594")
, (Text
"\\leftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8596")
, (Text
"\\uparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8593")
, (Text
"\\downarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8595")
, (Text
"\\updownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8597")
, (Text
"\\Leftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8656")
, (Text
"\\Rightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8658")
, (Text
"\\Leftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8660")
, (Text
"\\iff",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8660")
, (Text
"\\Uparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8657")
, (Text
"\\Downarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8659")
, (Text
"\\Updownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8661")
, (Text
"\\mapsto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8614")
, (Text
"\\longleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8592")
, (Text
"\\longrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8594")
, (Text
"\\longleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8596")
, (Text
"\\Longleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8656")
, (Text
"\\Longrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8658")
, (Text
"\\Longleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8660")
, (Text
"\\longmapsto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8614")
, (Text
"\\sum",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8721")
, (Text
"\\prod",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8719")
, (Text
"\\bigcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8898")
, (Text
"\\bigcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8899")
, (Text
"\\bigwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8896")
, (Text
"\\bigvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8897")
, (Text
"\\bigsqcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10757")
, (Text
"\\bigsqcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10758")
, (Text
"\\coprod",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8720")
, (Text
"\\bigoplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10753")
, (Text
"\\bigotimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10754")
, (Text
"\\bigodot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10752")
, (Text
"\\biguplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10756")
, (Text
"\\int",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8747")
, (Text
"\\iint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8748")
, (Text
"\\iiint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8749")
, (Text
"\\oint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8750")
, (Text
"\\prime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8242")
, (Text
"\\dots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
, (Text
"\\ldots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
, (Text
"\\hdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
, (Text
"\\cdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8943")
, (Text
"\\vdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8942")
, (Text
"\\ddots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8945")
, (Text
"\\forall",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8704")
, (Text
"\\exists",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8707")
, (Text
"\\Re",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8476")
, (Text
"\\Im",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8465")
, (Text
"\\aleph",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8501")
, (Text
"\\hbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8463")
, (Text
"\\ell",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8467")
, (Text
"\\wp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8472")
, (Text
"\\emptyset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8709")
, (Text
"\\infty",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8734")
, (Text
"\\partial",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8706")
, (Text
"\\nabla",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8711")
, (Text
"\\triangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9651")
, (Text
"\\therefore",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
"\8756")
, (Text
"\\angle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8736")
, (Text
"\\diamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8900")
, (Text
"\\Diamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\9671")
, (Text
"\\lozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\9674")
, (Text
"\\neg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\172")
, (Text
"\\lnot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\172")
, (Text
"\\bot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8869")
, (Text
"\\top",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8868")
, (Text
"\\square",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9643")
, (Text
"\\Box",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\9633")
, (Text
"\\wr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8768")
, (Text
"\\!",Rational -> Exp
ESpace ((-Integer
1) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
6))
, (Text
"\\,",Rational -> Exp
ESpace (Integer
1 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
6))
, (Text
"\\>",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
, (Text
"\\:",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
, (Text
"\\;",Rational -> Exp
ESpace (Integer
5 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
18))
, (Text
"\\ ",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
, (Text
"\\\n",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
9))
, (Text
"\\quad",Rational -> Exp
ESpace (Integer
1 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1))
, (Text
"\\qquad",Rational -> Exp
ESpace (Integer
2 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1))
, (Text
"\\arccos",Text -> Exp
EMathOperator Text
"arccos")
, (Text
"\\arcsin",Text -> Exp
EMathOperator Text
"arcsin")
, (Text
"\\arctan",Text -> Exp
EMathOperator Text
"arctan")
, (Text
"\\arg",Text -> Exp
EMathOperator Text
"arg")
, (Text
"\\cos",Text -> Exp
EMathOperator Text
"cos")
, (Text
"\\cosh",Text -> Exp
EMathOperator Text
"cosh")
, (Text
"\\cot",Text -> Exp
EMathOperator Text
"cot")
, (Text
"\\coth",Text -> Exp
EMathOperator Text
"coth")
, (Text
"\\csc",Text -> Exp
EMathOperator Text
"csc")
, (Text
"\\deg",Text -> Exp
EMathOperator Text
"deg")
, (Text
"\\det",Text -> Exp
EMathOperator Text
"det")
, (Text
"\\dim",Text -> Exp
EMathOperator Text
"dim")
, (Text
"\\exp",Text -> Exp
EMathOperator Text
"exp")
, (Text
"\\gcd",Text -> Exp
EMathOperator Text
"gcd")
, (Text
"\\hom",Text -> Exp
EMathOperator Text
"hom")
, (Text
"\\inf",Text -> Exp
EMathOperator Text
"inf")
, (Text
"\\ker",Text -> Exp
EMathOperator Text
"ker")
, (Text
"\\lg",Text -> Exp
EMathOperator Text
"lg")
, (Text
"\\lim",Text -> Exp
EMathOperator Text
"lim")
, (Text
"\\liminf",Text -> Exp
EMathOperator Text
"liminf")
, (Text
"\\limsup",Text -> Exp
EMathOperator Text
"limsup")
, (Text
"\\ln",Text -> Exp
EMathOperator Text
"ln")
, (Text
"\\log",Text -> Exp
EMathOperator Text
"log")
, (Text
"\\max",Text -> Exp
EMathOperator Text
"max")
, (Text
"\\min",Text -> Exp
EMathOperator Text
"min")
, (Text
"\\Pr",Text -> Exp
EMathOperator Text
"Pr")
, (Text
"\\sec",Text -> Exp
EMathOperator Text
"sec")
, (Text
"\\sin",Text -> Exp
EMathOperator Text
"sin")
, (Text
"\\sinh",Text -> Exp
EMathOperator Text
"sinh")
, (Text
"\\sup",Text -> Exp
EMathOperator Text
"sup")
, (Text
"\\tan",Text -> Exp
EMathOperator Text
"tan")
, (Text
"\\tanh",Text -> Exp
EMathOperator Text
"tanh")
, (Text
"\\AC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8767")
, (Text
"\\AC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9190")
, (Text
"\\APLboxquestion",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9072")
, (Text
"\\APLboxupcaret",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9043")
, (Text
"\\APLcomment",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9053")
, (Text
"\\APLdownarrowbox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9047")
, (Text
"\\APLinput",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9054")
, (Text
"\\APLinv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9017")
, (Text
"\\APLleftarrowbox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9031")
, (Text
"\\APLlog",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9055")
, (Text
"\\APLnotbackslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9024")
, (Text
"\\APLnotslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\9023")
, (Text
"\\APLrightarrowbox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9032")
, (Text
"\\APLuparrowbox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9040")
, (Text
"\\Angstroem",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8491")
, (Text
"\\Angstrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8491")
, (Text
"\\Aries",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9800")
, (Text
"\\Barv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10983")
, (Text
"\\BbbA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120120")
, (Text
"\\BbbB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120121")
, (Text
"\\BbbC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8450")
, (Text
"\\BbbD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120123")
, (Text
"\\BbbE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120124")
, (Text
"\\BbbF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120125")
, (Text
"\\BbbG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120126")
, (Text
"\\BbbGamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8510")
, (Text
"\\BbbH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8461")
, (Text
"\\BbbI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120128")
, (Text
"\\BbbJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120129")
, (Text
"\\BbbK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120130")
, (Text
"\\BbbL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120131")
, (Text
"\\BbbM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120132")
, (Text
"\\BbbN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8469")
, (Text
"\\BbbO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120134")
, (Text
"\\BbbP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8473")
, (Text
"\\BbbPi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8511")
, (Text
"\\BbbQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8474")
, (Text
"\\BbbR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8477")
, (Text
"\\BbbS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120138")
, (Text
"\\BbbT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120139")
, (Text
"\\BbbU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120140")
, (Text
"\\BbbV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120141")
, (Text
"\\BbbW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120142")
, (Text
"\\BbbX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120143")
, (Text
"\\BbbY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120144")
, (Text
"\\BbbZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8484")
, (Text
"\\Bbba",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120146")
, (Text
"\\Bbbb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120147")
, (Text
"\\Bbbc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120148")
, (Text
"\\Bbbd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120149")
, (Text
"\\Bbbe",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120150")
, (Text
"\\Bbbeight",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120800")
, (Text
"\\Bbbf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120151")
, (Text
"\\Bbbfive",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120797")
, (Text
"\\Bbbfour",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120796")
, (Text
"\\Bbbg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120152")
, (Text
"\\Bbbgamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8509")
, (Text
"\\Bbbh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120153")
, (Text
"\\Bbbi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120154")
, (Text
"\\Bbbj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120155")
, (Text
"\\Bbbk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120156")
, (Text
"\\Bbbl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120157")
, (Text
"\\Bbbm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120158")
, (Text
"\\Bbbn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120159")
, (Text
"\\Bbbnine",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120801")
, (Text
"\\Bbbo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120160")
, (Text
"\\Bbbone",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120793")
, (Text
"\\Bbbp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120161")
, (Text
"\\Bbbpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8508")
, (Text
"\\Bbbq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120162")
, (Text
"\\Bbbr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120163")
, (Text
"\\Bbbs",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120164")
, (Text
"\\Bbbseven",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120799")
, (Text
"\\Bbbsix",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120798")
, (Text
"\\Bbbsum",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8512")
, (Text
"\\Bbbt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120165")
, (Text
"\\Bbbthree",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120795")
, (Text
"\\Bbbtwo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120794")
, (Text
"\\Bbbu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120166")
, (Text
"\\Bbbv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120167")
, (Text
"\\Bbbw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120168")
, (Text
"\\Bbbx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120169")
, (Text
"\\Bbby",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120170")
, (Text
"\\Bbbz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120171")
, (Text
"\\Bbbzero",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120792")
, (Text
"\\Bot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10987")
, (Text
"\\Bumpeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8782")
, (Text
"\\CIRCLE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9679")
, (Text
"\\Cap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8914")
, (Text
"\\CapitalDifferentialD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8517")
, (Text
"\\CheckedBox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9745")
, (Text
"\\Circle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9675")
, (Text
"\\Colon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8759")
, (Text
"\\Coloneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10868")
, (Text
"\\Coloneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10868")
, (Text
"\\ComplexI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8520")
, (Text
"\\ComplexJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8521")
, (Text
"\\Cup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8915")
, (Text
"\\DD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8517")
, (Text
"\\DDDot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8411")
, (Text
"\\DDot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\776")
, (Text
"\\DDownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10225")
, (Text
"\\DashV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10981")
, (Text
"\\DashVDash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10202")
, (Text
"\\Dashv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10980")
, (Text
"\\Ddownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10507")
, (Text
"\\Diamondblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9670")
, (Text
"\\Diamonddot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10192")
, (Text
"\\DifferentialD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8518")
, (Text
"\\Digamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\988")
, (Text
"\\Dot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\775")
, (Text
"\\Doteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8785")
, (Text
"\\DownArrowBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10515")
, (Text
"\\DownLeftTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10590")
, (Text
"\\DownLeftVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10582")
, (Text
"\\DownRightTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10591")
, (Text
"\\DownRightVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10583")
, (Text
"\\Equal",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10869")
, (Text
"\\Equiv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8803")
, (Text
"\\Euler",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8455")
, (Text
"\\Eulerconst",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8455")
, (Text
"\\Exclam",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8252")
, (Text
"\\ExponetialE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8519")
, (Text
"\\Finv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8498")
, (Text
"\\Game",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8513")
, (Text
"\\Gemini",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9802")
, (Text
"\\GreaterLess",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8823")
, (Text
"\\Gt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10914")
, (Text
"\\HBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8463")
, (Text
"\\Hermaphrodite",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9893")
, (Text
"\\Jupiter",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9795")
, (Text
"\\Koppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\990")
, (Text
"\\Koppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\984")
, (Text
"\\LEFTCIRCLE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9686")
, (Text
"\\LEFTcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9680")
, (Text
"\\LHD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9664")
, (Text
"\\LLeftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11077")
, (Text
"\\LVec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8406")
, (Text
"\\Lbag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10181")
, (Text
"\\Lbrack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10214")
, (Text
"\\Lbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10220")
, (Text
"\\Lbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\12312")
, (Text
"\\Ldsh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8626")
, (Text
"\\LeftArrowBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8676")
, (Text
"\\LeftDownTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10593")
, (Text
"\\LeftDownVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10585")
, (Text
"\\LeftTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10586")
, (Text
"\\LeftTriangleBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10703")
, (Text
"\\LeftUpTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10592")
, (Text
"\\LeftUpVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10584")
, (Text
"\\LeftVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10578")
, (Text
"\\Leo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9804")
, (Text
"\\Libra",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9806")
, (Text
"\\Lleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8666")
, (Text
"\\Longmappedfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10237")
, (Text
"\\Longmapsfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10237")
, (Text
"\\Longmapsto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10238")
, (Text
"\\Lparen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10629")
, (Text
"\\Lparengtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10645")
, (Text
"\\Lsh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8624")
, (Text
"\\Lt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10913")
, (Text
"\\Lvzigzag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10714")
, (Text
"\\Mappedfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10502")
, (Text
"\\MapsDown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8615")
, (Text
"\\MapsUp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8613")
, (Text
"\\Mapsfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10502")
, (Text
"\\Mapsto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10503")
, (Text
"\\Mars",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9794")
, (Text
"\\Mercury",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9791")
, (Text
"\\Mho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8487")
, (Text
"\\Micro",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\181")
, (Text
"\\Nearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8663")
, (Text
"\\Neptune",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9798")
, (Text
"\\NestedGreaterGreater",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10914")
, (Text
"\\NestedLessLess",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10913")
, (Text
"\\Not",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10988")
, (Text
"\\NotGreaterLess",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8825")
, (Text
"\\NotGreaterTilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8821")
, (Text
"\\NotLeftTriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8938")
, (Text
"\\NotLessTilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8820")
, (Text
"\\NotRightTriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8939")
, (Text
"\\Nwarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8662")
, (Text
"\\Otimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10807")
, (Text
"\\Perp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10987")
, (Text
"\\Planckconst",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8462")
, (Text
"\\Pluto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9799")
, (Text
"\\Prec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10939")
, (Text
"\\PrecedesSlantEqual",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8828")
, (Text
"\\PrecedesTilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8830")
, (Text
"\\PropertyLine",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8522")
, (Text
"\\Proportion",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8759")
, (Text
"\\QED",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8718")
, (Text
"\\Qoppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\984")
, (Text
"\\Question",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8263")
, (Text
"\\RHD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9654")
, (Text
"\\RIGHTCIRCLE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9687")
, (Text
"\\RIGHTcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9681")
, (Text
"\\RRightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11078")
, (Text
"\\Rbag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10182")
, (Text
"\\Rbrack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10215")
, (Text
"\\Rbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10221")
, (Text
"\\Rbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\12313")
, (Text
"\\Rdsh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8627")
, (Text
"\\RightArrowBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8677")
, (Text
"\\RightDownTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10589")
, (Text
"\\RightDownVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10581")
, (Text
"\\RightTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10587")
, (Text
"\\RightTriangleBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10704")
, (Text
"\\RightUpTeeVector",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10588")
, (Text
"\\RightUpVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10580")
, (Text
"\\RightVectorBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10579")
, (Text
"\\Rparen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10630")
, (Text
"\\Rparenless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10646")
, (Text
"\\Rrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8667")
, (Text
"\\Rsh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8625")
, (Text
"\\Rvzigzag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10715")
, (Text
"\\Same",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10870")
, (Text
"\\Sampi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\992")
, (Text
"\\Saturn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9796")
, (Text
"\\Scorpio",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9807")
, (Text
"\\Searrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8664")
, (Text
"\\Sqcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10830")
, (Text
"\\Sqcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10831")
, (Text
"\\Square",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9744")
, (Text
"\\Stigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\986")
, (Text
"\\Subset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8912")
, (Text
"\\Succ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10940")
, (Text
"\\SucceedsSlantEqual",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8829")
, (Text
"\\SucceedsTilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8831")
, (Text
"\\Sun",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9737")
, (Text
"\\Supset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8913")
, (Text
"\\Swarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8665")
, (Text
"\\Taurus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9801")
, (Text
"\\Top",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10986")
, (Text
"\\UUparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10224")
, (Text
"\\UpArrowBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10514")
, (Text
"\\Uranus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9797")
, (Text
"\\Uuparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10506")
, (Text
"\\VDash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8875")
, (Text
"\\VERT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Fence Text
"\10624")
, (Text
"\\Vbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10987")
, (Text
"\\Vdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8873")
, (Text
"\\Vec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8407")
, (Text
"\\Vee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10836")
, (Text
"\\Venus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9792")
, (Text
"\\Vert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Fence Text
"\8214")
, (Text
"\\Vvdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8874")
, (Text
"\\Vvert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Fence Text
"\10624")
, (Text
"\\Wedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10835")
, (Text
"\\XBox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9746")
, (Text
"\\Yup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8516")
, (Text
"\\Zbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\437")
, (Text
"\\accurrent",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9190")
, (Text
"\\acidfree",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9854")
, (Text
"\\acute",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\769")
, (Text
"\\acwcirclearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10560")
, (Text
"\\acwgapcirclearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10226")
, (Text
"\\acwleftarcarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10553")
, (Text
"\\acwopencirclearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8634")
, (Text
"\\acwoverarcarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10554")
, (Text
"\\acwunderarcarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10555")
, (Text
"\\adots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8944")
, (Text
"\\ampersand",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"&")
, (Text
"\\anchor",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9875")
, (Text
"\\angdnr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10655")
, (Text
"\\angles",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10654")
, (Text
"\\angleubar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10660")
, (Text
"\\annuity",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8423")
, (Text
"\\apprge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8819")
, (Text
"\\apprle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8818")
, (Text
"\\approxeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8778")
, (Text
"\\approxeqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10864")
, (Text
"\\approxident",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8779")
, (Text
"\\aquarius",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9810")
, (Text
"\\arceq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8792")
, (Text
"\\aries",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9800")
, (Text
"\\arrowbullet",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10146")
, (Text
"\\assert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8870")
, (Text
"\\asteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10862")
, (Text
"\\asteraccent",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8432")
, (Text
"\\astrosun",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9737")
, (Text
"\\atsign",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"@")
, (Text
"\\awint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10769")
, (Text
"\\bNot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10989")
, (Text
"\\backcong",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8780")
, (Text
"\\backdprime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8246")
, (Text
"\\backepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\1014")
, (Text
"\\backprime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8245")
, (Text
"\\backsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8765")
, (Text
"\\backsimeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8909")
, (Text
"\\backtrprime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8247")
, (Text
"\\bagmember",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8959")
, (Text
"\\ballotcheck",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10003")
, (Text
"\\ballotx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10007")
, (Text
"\\bar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8254")
, (Text
"\\barV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10986")
, (Text
"\\barcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10819")
, (Text
"\\barcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10818")
, (Text
"\\bardownharpoonleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10593")
, (Text
"\\bardownharpoonright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10589")
, (Text
"\\barin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8950")
, (Text
"\\barleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8676")
, (Text
"\\barleftarrowrightarrowba",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8633")
, (Text
"\\barleftharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10603")
, (Text
"\\barleftharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10582")
, (Text
"\\barleftharpoonup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10578")
, (Text
"\\barovernorthwestarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8632")
, (Text
"\\barrightarrowdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10528")
, (Text
"\\barrightharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10605")
, (Text
"\\barrightharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10591")
, (Text
"\\barrightharpoonup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10587")
, (Text
"\\baruparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10514")
, (Text
"\\barupharpoonleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10584")
, (Text
"\\barupharpoonright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10580")
, (Text
"\\barvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8893")
, (Text
"\\barwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8892")
, (Text
"\\barwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8965")
, (Text
"\\bbrktbrk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9142")
, (Text
"\\bdtriplevdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9478")
, (Text
"\\because",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8757")
, (Text
"\\benzenr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9187")
, (Text
"\\beth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8502")
, (Text
"\\between",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8812")
, (Text
"\\bigblacktriangledown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9660")
, (Text
"\\bigblacktriangleup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9650")
, (Text
"\\bigbot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10200")
, (Text
"\\bigcupdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10755")
, (Text
"\\biginterleave",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\11004")
, (Text
"\\bigslopedvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10839")
, (Text
"\\bigslopedwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10840")
, (Text
"\\bigstar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9733")
, (Text
"\\bigtalloblong",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\11007")
, (Text
"\\bigtimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10761")
, (Text
"\\bigtop",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10201")
, (Text
"\\bigtriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10782")
, (Text
"\\bigwhitestar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9734")
, (Text
"\\bij",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10518")
, (Text
"\\binampersand",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"&")
, (Text
"\\bindnasrepma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8523")
, (Text
"\\biohazard",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9763")
, (Text
"\\blackcircledownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10733")
, (Text
"\\blackcircledrightdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9864")
, (Text
"\\blackcircledtwodots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9865")
, (Text
"\\blackcircleulquadwhite",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9685")
, (Text
"\\blackdiamonddownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10730")
, (Text
"\\blackhourglass",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10711")
, (Text
"\\blackinwhitediamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9672")
, (Text
"\\blackinwhitesquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9635")
, (Text
"\\blacklefthalfcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9686")
, (Text
"\\blacklozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10731")
, (Text
"\\blacklozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11047")
, (Text
"\\blackpointerleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9668")
, (Text
"\\blackpointerright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9658")
, (Text
"\\blackrighthalfcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9687")
, (Text
"\\blacksmiley",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9787")
, (Text
"\\blacksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11035")
, (Text
"\\blacksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8718")
, (Text
"\\blacksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9632")
, (Text
"\\blacksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9724")
, (Text
"\\blacktriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9652")
, (Text
"\\blacktriangledown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9662")
, (Text
"\\blacktriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9664")
, (Text
"\\blacktriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9666")
, (Text
"\\blacktriangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9654")
, (Text
"\\blacktriangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9656")
, (Text
"\\blacktriangleup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9652")
, (Text
"\\blkhorzoval",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11052")
, (Text
"\\blkvertoval",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11054")
, (Text
"\\blockfull",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9608")
, (Text
"\\blockhalfshaded",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9618")
, (Text
"\\blocklefthalf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9612")
, (Text
"\\blocklowhalf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9604")
, (Text
"\\blockqtrshaded",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9617")
, (Text
"\\blockrighthalf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9616")
, (Text
"\\blockthreeqtrshaded",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9619")
, (Text
"\\blockuphalf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9600")
, (Text
"\\botsemicircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9697")
, (Text
"\\boxast",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10694")
, (Text
"\\boxbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9707")
, (Text
"\\boxbox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10696")
, (Text
"\\boxbslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10693")
, (Text
"\\boxcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10695")
, (Text
"\\boxdiag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10692")
, (Text
"\\boxdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8865")
, (Text
"\\boxminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8863")
, (Text
"\\boxonbox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10697")
, (Text
"\\boxplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8862")
, (Text
"\\boxslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10692")
, (Text
"\\boxtimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8864")
, (Text
"\\breve",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\774")
, (Text
"\\bsimilarleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11073")
, (Text
"\\bsimilarrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11079")
, (Text
"\\bsolhsub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10184")
, (Text
"\\btimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10802")
, (Text
"\\bullseye",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9678")
, (Text
"\\bumpeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8783")
, (Text
"\\bumpeqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10926")
, (Text
"\\buni",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8846")
, (Text
"\\cancer",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9803")
, (Text
"\\candra",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\784")
, (Text
"\\capbarcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10825")
, (Text
"\\capdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10816")
, (Text
"\\capovercup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10823")
, (Text
"\\capricornus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9809")
, (Text
"\\capwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10820")
, (Text
"\\caretinsert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8248")
, (Text
"\\carriagereturn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8629")
, (Text
"\\cat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8256")
, (Text
"\\ccwundercurvearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10559")
, (Text
"\\cdotp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\183")
, (Text
"\\cent",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\162")
, (Text
"\\centerdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11037")
, (Text
"\\check",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\780")
, (Text
"\\checkmark",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10003")
, (Text
"\\cirE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10691")
, (Text
"\\cirbot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10207")
, (Text
"\\circeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8791")
, (Text
"\\circlearrowleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8634")
, (Text
"\\circlearrowright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8635")
, (Text
"\\circlebottomhalfblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9682")
, (Text
"\\circledR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\174")
, (Text
"\\circledast",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8859")
, (Text
"\\circledbslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10680")
, (Text
"\\circledbullet",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10687")
, (Text
"\\circledcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8858")
, (Text
"\\circledcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9678")
, (Text
"\\circleddash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8861")
, (Text
"\\circledequal",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8860")
, (Text
"\\circledgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10689")
, (Text
"\\circledless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10688")
, (Text
"\\circledownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10732")
, (Text
"\\circledparallel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10679")
, (Text
"\\circledrightdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9862")
, (Text
"\\circledstar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10026")
, (Text
"\\circledtwodots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9863")
, (Text
"\\circledvert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10678")
, (Text
"\\circledwhitebullet",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10686")
, (Text
"\\circlehbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10677")
, (Text
"\\circlelefthalfblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9680")
, (Text
"\\circlellquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9717")
, (Text
"\\circlelrquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9718")
, (Text
"\\circleonleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11056")
, (Text
"\\circleonrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8692")
, (Text
"\\circlerighthalfblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9681")
, (Text
"\\circletophalfblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9683")
, (Text
"\\circleulquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9716")
, (Text
"\\circleurquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9719")
, (Text
"\\circleurquadblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9684")
, (Text
"\\circlevertfill",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9677")
, (Text
"\\cirfnint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10768")
, (Text
"\\cirmid",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10991")
, (Text
"\\cirscir",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10690")
, (Text
"\\clockoint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8754")
, (Text
"\\closedvarcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10829")
, (Text
"\\closedvarcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10828")
, (Text
"\\closedvarcupsmashprod",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10832")
, (Text
"\\closure",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8272")
, (Text
"\\clubsuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9827")
, (Text
"\\cntclockoint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8755")
, (Text
"\\coloneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8788")
, (Text
"\\coloneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8788")
, (Text
"\\comma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
",")
, (Text
"\\commaminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10793")
, (Text
"\\comp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10814")
, (Text
"\\complement",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8705")
, (Text
"\\concavediamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10209")
, (Text
"\\concavediamondtickleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10210")
, (Text
"\\concavediamondtickright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10211")
, (Text
"\\congdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10861")
, (Text
"\\conictaper",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9010")
, (Text
"\\conjquant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10759")
, (Text
"\\corresponds",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8793")
, (Text
"\\csub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10959")
, (Text
"\\csube",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10961")
, (Text
"\\csup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10960")
, (Text
"\\csupe",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10962")
, (Text
"\\cuberoot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rad Text
"\8731")
, (Text
"\\cupbarcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10824")
, (Text
"\\cupdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8845")
, (Text
"\\cupleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8844")
, (Text
"\\cupovercap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10822")
, (Text
"\\cupvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10821")
, (Text
"\\curlyeqprec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8926")
, (Text
"\\curlyeqsucc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8927")
, (Text
"\\curlyvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8910")
, (Text
"\\curlywedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8911")
, (Text
"\\curvearrowleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8630")
, (Text
"\\curvearrowleftplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10557")
, (Text
"\\curvearrowright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8631")
, (Text
"\\curvearrowrightminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10556")
, (Text
"\\cwcirclearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10561")
, (Text
"\\cwgapcirclearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10227")
, (Text
"\\cwopencirclearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8635")
, (Text
"\\cwrightarcarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10552")
, (Text
"\\cwundercurvearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10558")
, (Text
"\\daleth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8504")
, (Text
"\\danger",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9761")
, (Text
"\\dashV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10979")
, (Text
"\\dashVdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10203")
, (Text
"\\dasharrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8674")
, (Text
"\\dashcolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8761")
, (Text
"\\dashleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8672")
, (Text
"\\dashleftharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10603")
, (Text
"\\dashrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8674")
, (Text
"\\dashrightharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10605")
, (Text
"\\dbkarow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10511")
, (Text
"\\dbloint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8751")
, (Text
"\\dd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8518")
, (Text
"\\ddddot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8412")
, (Text
"\\dddot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8411")
, (Text
"\\ddot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\776")
, (Text
"\\ddotseq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10871")
, (Text
"\\diameter",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8960")
, (Text
"\\diamondbotblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11033")
, (Text
"\\diamondcdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10192")
, (Text
"\\diamondleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10525")
, (Text
"\\diamondleftarrowbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10527")
, (Text
"\\diamondleftblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11030")
, (Text
"\\diamondrightblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11031")
, (Text
"\\diamondsuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9826")
, (Text
"\\diamondtopblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11032")
, (Text
"\\dicei",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9856")
, (Text
"\\diceii",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9857")
, (Text
"\\diceiii",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9858")
, (Text
"\\diceiv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9859")
, (Text
"\\dicev",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9860")
, (Text
"\\dicevi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9861")
, (Text
"\\digamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\988")
, (Text
"\\digamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\989")
, (Text
"\\dingasterisk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10045")
, (Text
"\\dint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8898")
, (Text
"\\disin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8946")
, (Text
"\\disjquant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10760")
, (Text
"\\divideontimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8903")
, (Text
"\\divslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8725")
, (Text
"\\dlsh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8626")
, (Text
"\\dot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\775")
, (Text
"\\doteqdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8785")
, (Text
"\\dotequal",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8784")
, (Text
"\\dotequiv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10855")
, (Text
"\\dotminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8760")
, (Text
"\\dotplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8724")
, (Text
"\\dotsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10858")
, (Text
"\\dotsminusdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8762")
, (Text
"\\dottedcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9676")
, (Text
"\\dottedsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11034")
, (Text
"\\dottimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10800")
, (Text
"\\doublebarvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10850")
, (Text
"\\doublebarwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10846")
, (Text
"\\doublebarwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8966")
, (Text
"\\doubleplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10746")
, (Text
"\\downarrowbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10515")
, (Text
"\\downarrowbarred",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10504")
, (Text
"\\downarrowuparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8693")
, (Text
"\\downdasharrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8675")
, (Text
"\\downdownarrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8650")
, (Text
"\\downdownharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10597")
, (Text
"\\downfishtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10623")
, (Text
"\\downharpoonleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8643")
, (Text
"\\downharpoonleftbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10585")
, (Text
"\\downharpoonright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8642")
, (Text
"\\downharpoonrightbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10581")
, (Text
"\\downharpoonsleftright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10597")
, (Text
"\\downrightcurvedarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10549")
, (Text
"\\downtriangleleftblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10728")
, (Text
"\\downtrianglerightblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10729")
, (Text
"\\downuparrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8693")
, (Text
"\\downupharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10607")
, (Text
"\\downupharpoonsleftright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10607")
, (Text
"\\downwhitearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8681")
, (Text
"\\downzigzagarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8623")
, (Text
"\\dprime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8243")
, (Text
"\\draftingarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10139")
, (Text
"\\drbkarow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10512")
, (Text
"\\dres",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9665")
, (Text
"\\droang",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\794")
, (Text
"\\drsh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8627")
, (Text
"\\dsol",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10742")
, (Text
"\\dsub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10852")
, (Text
"\\dualmap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10719")
, (Text
"\\duni",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8899")
, (Text
"\\earth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9793")
, (Text
"\\ee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8519")
, (Text
"\\egsdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10904")
, (Text
"\\eighthnote",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9834")
, (Text
"\\elinters",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9191")
, (Text
"\\elsdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10903")
, (Text
"\\emptysetoarr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10675")
, (Text
"\\emptysetoarrl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10676")
, (Text
"\\emptysetobar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10673")
, (Text
"\\emptysetocirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10674")
, (Text
"\\enclosecircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8413")
, (Text
"\\enclosediamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8415")
, (Text
"\\enclosesquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8414")
, (Text
"\\enclosetriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8420")
, (Text
"\\enleadertwodots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8229")
, (Text
"\\eparsl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10723")
, (Text
"\\eqcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8790")
, (Text
"\\eqcolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8761")
, (Text
"\\eqcolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8789")
, (Text
"\\eqdef",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8797")
, (Text
"\\eqdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10854")
, (Text
"\\eqeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10869")
, (Text
"\\eqeqeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10870")
, (Text
"\\eqgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8925")
, (Text
"\\eqless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8924")
, (Text
"\\eqqcolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8789")
, (Text
"\\eqqgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10906")
, (Text
"\\eqqless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10905")
, (Text
"\\eqqplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10865")
, (Text
"\\eqqsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10867")
, (Text
"\\eqqslantgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10908")
, (Text
"\\eqqslantless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10907")
, (Text
"\\eqsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8770")
, (Text
"\\eqslantgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10902")
, (Text
"\\eqslantless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10901")
, (Text
"\\equal",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"=")
, (Text
"\\equalleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11072")
, (Text
"\\equalparallel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8917")
, (Text
"\\equalrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10609")
, (Text
"\\equilibrium",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8652")
, (Text
"\\equivDD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10872")
, (Text
"\\equivVert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10856")
, (Text
"\\equivVvert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10857")
, (Text
"\\eqvparsl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10725")
, (Text
"\\errbarblackcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10739")
, (Text
"\\errbarblackdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10737")
, (Text
"\\errbarblacksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10735")
, (Text
"\\errbarcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10738")
, (Text
"\\errbardiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10736")
, (Text
"\\errbarsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10734")
, (Text
"\\eth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\240")
, (Text
"\\euro",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8364")
, (Text
"\\exclam",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
"!")
, (Text
"\\exi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8707")
, (Text
"\\fallingdotseq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8786")
, (Text
"\\fbowtie",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10707")
, (Text
"\\fcmp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10814")
, (Text
"\\fdiagovnearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10543")
, (Text
"\\fdiagovrdiag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10540")
, (Text
"\\female",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9792")
, (Text
"\\ffun",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8699")
, (Text
"\\finj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10517")
, (Text
"\\fint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10767")
, (Text
"\\fisheye",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9673")
, (Text
"\\flat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9837")
, (Text
"\\fltns",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9189")
, (Text
"\\forks",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10972")
, (Text
"\\forksnot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10973")
, (Text
"\\forkv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10969")
, (Text
"\\fourth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8279")
, (Text
"\\fourthroot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rad Text
"\8732")
, (Text
"\\fourvdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10649")
, (Text
"\\fracslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8260")
, (Text
"\\frownie",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9785")
, (Text
"\\fullouterjoin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10199")
, (Text
"\\gemini",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9802")
, (Text
"\\geqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8807")
, (Text
"\\geqqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11002")
, (Text
"\\gescc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10921")
, (Text
"\\gesdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10880")
, (Text
"\\gesdoto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10882")
, (Text
"\\gesdotol",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10884")
, (Text
"\\gesles",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10900")
, (Text
"\\ggcurly",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10940")
, (Text
"\\ggg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10914")
, (Text
"\\ggg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8921")
, (Text
"\\gggnest",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11000")
, (Text
"\\gimel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8503")
, (Text
"\\glE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10898")
, (Text
"\\gla",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10917")
, (Text
"\\gleichstark",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10726")
, (Text
"\\glj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10916")
, (Text
"\\gnapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10890")
, (Text
"\\gneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10888")
, (Text
"\\gneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8809")
, (Text
"\\gnsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8935")
, (Text
"\\grave",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\768")
, (Text
"\\greater",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
">")
, (Text
"\\gsime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10894")
, (Text
"\\gsiml",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10896")
, (Text
"\\gtcc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10919")
, (Text
"\\gtcir",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10874")
, (Text
"\\gtlpar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10656")
, (Text
"\\gtquest",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10876")
, (Text
"\\gtrapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10886")
, (Text
"\\gtrarr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10616")
, (Text
"\\gtrdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8919")
, (Text
"\\gtreqless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8923")
, (Text
"\\gtreqqless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10892")
, (Text
"\\gtrless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8823")
, (Text
"\\gtrsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8819")
, (Text
"\\harrowextender",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9135")
, (Text
"\\hash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8917")
, (Text
"\\hat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\770")
, (Text
"\\hatapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10863")
, (Text
"\\heartsuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9825")
, (Text
"\\hermitmatrix",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8889")
, (Text
"\\hexagon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9108")
, (Text
"\\hexagonblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11043")
, (Text
"\\hide",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10745")
, (Text
"\\hknearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10532")
, (Text
"\\hknwarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10531")
, (Text
"\\hksearow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10533")
, (Text
"\\hkswarow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10534")
, (Text
"\\hookleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8617")
, (Text
"\\hookrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8618")
, (Text
"\\horizbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8213")
, (Text
"\\hourglass",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10710")
, (Text
"\\house",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8962")
, (Text
"\\hrectangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9645")
, (Text
"\\hrectangleblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9644")
, (Text
"\\hslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8463")
, (Text
"\\hyphenbullet",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8259")
, (Text
"\\hzigzag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\12336")
, (Text
"\\iddots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8944")
, (Text
"\\ii",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8520")
, (Text
"\\iiiint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10764")
, (Text
"\\iinfin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10716")
, (Text
"\\imageof",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8887")
, (Text
"\\imath",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120484")
, (Text
"\\imath",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\305")
, (Text
"\\impliedby",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10232")
, (Text
"\\implies",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10233")
, (Text
"\\increment",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8710")
, (Text
"\\intBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10766")
, (Text
"\\intbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10765")
, (Text
"\\intbottom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8993")
, (Text
"\\intcap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10777")
, (Text
"\\intclockwise",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8753")
, (Text
"\\intcup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10778")
, (Text
"\\intercal",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8890")
, (Text
"\\interleave",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10996")
, (Text
"\\intextender",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9134")
, (Text
"\\intlarhk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10775")
, (Text
"\\intprod",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10812")
, (Text
"\\intprodr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10813")
, (Text
"\\inttop",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8992")
, (Text
"\\intx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10776")
, (Text
"\\invamp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8523")
, (Text
"\\inversebullet",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9688")
, (Text
"\\inversewhitecircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9689")
, (Text
"\\invlazys",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8766")
, (Text
"\\invneg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8976")
, (Text
"\\invnot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8976")
, (Text
"\\invsmileface",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9787")
, (Text
"\\invwhitelowerhalfcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9691")
, (Text
"\\invwhiteupperhalfcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9690")
, (Text
"\\isinE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8953")
, (Text
"\\isindot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8949")
, (Text
"\\isinobar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8951")
, (Text
"\\isins",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8948")
, (Text
"\\isinvb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8952")
, (Text
"\\jj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8521")
, (Text
"\\jmath",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120485")
, (Text
"\\jmath",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\567")
, (Text
"\\jupiter",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9795")
, (Text
"\\kernelcontraction",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8763")
, (Text
"\\koppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\991")
, (Text
"\\koppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\985")
, (Text
"\\lAngle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10218")
, (Text
"\\lBrace",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10627")
, (Text
"\\lBrack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10214")
, (Text
"\\lParen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10629")
, (Text
"\\lang",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10218")
, (Text
"\\langle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10216")
, (Text
"\\langle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\12296")
, (Text
"\\langle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\9001")
, (Text
"\\langledot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10641")
, (Text
"\\laplac",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10720")
, (Text
"\\lat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10923")
, (Text
"\\late",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10925")
, (Text
"\\lbag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10181")
, (Text
"\\lblkbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10647")
, (Text
"\\lblot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10633")
, (Text
"\\lbrace",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"{")
, (Text
"\\lbracelend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9129")
, (Text
"\\lbracemid",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9128")
, (Text
"\\lbraceuend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9127")
, (Text
"\\lbrack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"[")
, (Text
"\\lbrackextender",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9122")
, (Text
"\\lbracklend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9123")
, (Text
"\\lbracklltick",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10639")
, (Text
"\\lbrackubar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10635")
, (Text
"\\lbrackuend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9121")
, (Text
"\\lbrackultick",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10637")
, (Text
"\\lbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10098")
, (Text
"\\lbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\12308")
, (Text
"\\lceil",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\8968")
, (Text
"\\lcurvyangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10748")
, (Text
"\\leadsto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10547")
, (Text
"\\leftarrowapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11082")
, (Text
"\\leftarrowbackapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11074")
, (Text
"\\leftarrowbsimilar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11083")
, (Text
"\\leftarrowless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10615")
, (Text
"\\leftarrowonoplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11058")
, (Text
"\\leftarrowplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10566")
, (Text
"\\leftarrowshortrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10563")
, (Text
"\\leftarrowsimilar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10611")
, (Text
"\\leftarrowsubset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10618")
, (Text
"\\leftarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8610")
, (Text
"\\leftarrowtriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8701")
, (Text
"\\leftarrowx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11070")
, (Text
"\\leftbarharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10602")
, (Text
"\\leftbkarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10508")
, (Text
"\\leftcurvedarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11071")
, (Text
"\\leftdasharrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8672")
, (Text
"\\leftdbkarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10510")
, (Text
"\\leftdbltail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10523")
, (Text
"\\leftdotarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11064")
, (Text
"\\leftdowncurvedarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10550")
, (Text
"\\leftfishtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10620")
, (Text
"\\leftharpoonaccent",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8400")
, (Text
"\\leftharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8637")
, (Text
"\\leftharpoondownbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10590")
, (Text
"\\leftharpoonsupdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10594")
, (Text
"\\leftharpoonup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8636")
, (Text
"\\leftharpoonupbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10586")
, (Text
"\\leftharpoonupdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10602")
, (Text
"\\leftleftarrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8647")
, (Text
"\\leftleftharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10594")
, (Text
"\\leftmoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9790")
, (Text
"\\leftouterjoin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10197")
, (Text
"\\leftrightarrowcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10568")
, (Text
"\\leftrightarrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8646")
, (Text
"\\leftrightarrowtriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8703")
, (Text
"\\leftrightharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10570")
, (Text
"\\leftrightharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10576")
, (Text
"\\leftrightharpoondowndown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10576")
, (Text
"\\leftrightharpoondownup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10571")
, (Text
"\\leftrightharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8651")
, (Text
"\\leftrightharpoonsdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10599")
, (Text
"\\leftrightharpoonsup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10598")
, (Text
"\\leftrightharpoonup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10574")
, (Text
"\\leftrightharpoonupdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10570")
, (Text
"\\leftrightharpoonupup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10574")
, (Text
"\\leftrightsquigarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8621")
, (Text
"\\leftslice",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10918")
, (Text
"\\leftsquigarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8668")
, (Text
"\\lefttail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10521")
, (Text
"\\leftthreearrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11057")
, (Text
"\\leftthreetimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8907")
, (Text
"\\leftturn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8634")
, (Text
"\\leftupdownharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10577")
, (Text
"\\leftwavearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8604")
, (Text
"\\leftwhitearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8678")
, (Text
"\\leo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9804")
, (Text
"\\leqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8806")
, (Text
"\\leqqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11001")
, (Text
"\\lescc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10920")
, (Text
"\\lesdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10879")
, (Text
"\\lesdoto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10881")
, (Text
"\\lesdotor",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10883")
, (Text
"\\lesges",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10899")
, (Text
"\\less",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"<")
, (Text
"\\lessapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10885")
, (Text
"\\lessdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8918")
, (Text
"\\lesseqgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8922")
, (Text
"\\lesseqqgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10891")
, (Text
"\\lessgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8822")
, (Text
"\\lesssim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8818")
, (Text
"\\lfbowtie",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10705")
, (Text
"\\lfloor",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\8970")
, (Text
"\\lftimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10708")
, (Text
"\\lgE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10897")
, (Text
"\\lgblkcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11044")
, (Text
"\\lgblksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11035")
, (Text
"\\lgroup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10222")
, (Text
"\\lgwhtcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9711")
, (Text
"\\lgwhtsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11036")
, (Text
"\\libra",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9806")
, (Text
"\\lightning",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8623")
, (Text
"\\limg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10631")
, (Text
"\\linefeed",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8628")
, (Text
"\\llangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10633")
, (Text
"\\llarc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9695")
, (Text
"\\llblacktriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9699")
, (Text
"\\llbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10214")
, (Text
"\\llbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\12314")
, (Text
"\\llcorner",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\8990")
, (Text
"\\llcurly",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10939")
, (Text
"\\lll",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10913")
, (Text
"\\lll",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8920")
, (Text
"\\lllnest",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10999")
, (Text
"\\llparenthesis",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10631")
, (Text
"\\lltriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9722")
, (Text
"\\lmoustache",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9136")
, (Text
"\\lnapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10889")
, (Text
"\\lneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10887")
, (Text
"\\lneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8808")
, (Text
"\\lnsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8934")
, (Text
"\\longdashv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10206")
, (Text
"\\longdivision",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10188")
, (Text
"\\longleftsquigarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11059")
, (Text
"\\longmappedfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10235")
, (Text
"\\longmapsfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10235")
, (Text
"\\longrightsquigarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10239")
, (Text
"\\looparrowleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8619")
, (Text
"\\looparrowright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8620")
, (Text
"\\lowint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10780")
, (Text
"\\lozengeminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10208")
, (Text
"\\lparen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"(")
, (Text
"\\lparenextender",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9116")
, (Text
"\\lparenlend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9117")
, (Text
"\\lparenless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10643")
, (Text
"\\lparenuend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9115")
, (Text
"\\lrarc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9694")
, (Text
"\\lrblacktriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9698")
, (Text
"\\lrcorner",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\8991")
, (Text
"\\lrtimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8904")
, (Text
"\\lrtriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9727")
, (Text
"\\lrtriangleeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10721")
, (Text
"\\lsime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10893")
, (Text
"\\lsimg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10895")
, (Text
"\\lsqhook",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10957")
, (Text
"\\ltcc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10918")
, (Text
"\\ltcir",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10873")
, (Text
"\\ltlarr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10614")
, (Text
"\\ltquest",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10875")
, (Text
"\\ltrivb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10703")
, (Text
"\\lvboxline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9144")
, (Text
"\\lvec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8400")
, (Text
"\\lvzigzag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\10712")
, (Text
"\\male",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9794")
, (Text
"\\maltese",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10016")
, (Text
"\\mappedfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8612")
, (Text
"\\mapsdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8615")
, (Text
"\\mapsfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8612")
, (Text
"\\mapsup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8613")
, (Text
"\\mathcent",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\162")
, (Text
"\\mathcolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
":")
, (Text
"\\mathdollar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"$")
, (Text
"\\matheth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\240")
, (Text
"\\mathratio",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8758")
, (Text
"\\mathring",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\778")
, (Text
"\\mathslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"/")
, (Text
"\\mathsterling",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\163")
, (Text
"\\mbfA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119808")
, (Text
"\\mbfAlpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120488")
, (Text
"\\mbfB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119809")
, (Text
"\\mbfBeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120489")
, (Text
"\\mbfC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119810")
, (Text
"\\mbfChi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120510")
, (Text
"\\mbfD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119811")
, (Text
"\\mbfDelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120491")
, (Text
"\\mbfDigamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120778")
, (Text
"\\mbfE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119812")
, (Text
"\\mbfEpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120492")
, (Text
"\\mbfEta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120494")
, (Text
"\\mbfF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119813")
, (Text
"\\mbfG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119814")
, (Text
"\\mbfGamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120490")
, (Text
"\\mbfH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119815")
, (Text
"\\mbfI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119816")
, (Text
"\\mbfIota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120496")
, (Text
"\\mbfJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119817")
, (Text
"\\mbfK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119818")
, (Text
"\\mbfKappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120497")
, (Text
"\\mbfL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119819")
, (Text
"\\mbfLambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120498")
, (Text
"\\mbfM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119820")
, (Text
"\\mbfMu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120499")
, (Text
"\\mbfN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119821")
, (Text
"\\mbfNu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120500")
, (Text
"\\mbfO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119822")
, (Text
"\\mbfOmega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120512")
, (Text
"\\mbfOmicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120502")
, (Text
"\\mbfP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119823")
, (Text
"\\mbfPhi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120509")
, (Text
"\\mbfPi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120503")
, (Text
"\\mbfPsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120511")
, (Text
"\\mbfQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119824")
, (Text
"\\mbfR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119825")
, (Text
"\\mbfRho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120504")
, (Text
"\\mbfS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119826")
, (Text
"\\mbfSigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120506")
, (Text
"\\mbfT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119827")
, (Text
"\\mbfTau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120507")
, (Text
"\\mbfTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120495")
, (Text
"\\mbfU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119828")
, (Text
"\\mbfUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120508")
, (Text
"\\mbfV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119829")
, (Text
"\\mbfW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119830")
, (Text
"\\mbfX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119831")
, (Text
"\\mbfXi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120501")
, (Text
"\\mbfY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119832")
, (Text
"\\mbfZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119833")
, (Text
"\\mbfZeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120493")
, (Text
"\\mbfa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119834")
, (Text
"\\mbfalpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120514")
, (Text
"\\mbfb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119835")
, (Text
"\\mbfbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120515")
, (Text
"\\mbfc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119836")
, (Text
"\\mbfchi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120536")
, (Text
"\\mbfd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119837")
, (Text
"\\mbfdelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120517")
, (Text
"\\mbfdigamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120779")
, (Text
"\\mbfe",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119838")
, (Text
"\\mbfepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120518")
, (Text
"\\mbfeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120520")
, (Text
"\\mbff",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119839")
, (Text
"\\mbffrakA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120172")
, (Text
"\\mbffrakB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120173")
, (Text
"\\mbffrakC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120174")
, (Text
"\\mbffrakD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120175")
, (Text
"\\mbffrakE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120176")
, (Text
"\\mbffrakF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120177")
, (Text
"\\mbffrakG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120178")
, (Text
"\\mbffrakH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120179")
, (Text
"\\mbffrakI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120180")
, (Text
"\\mbffrakJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120181")
, (Text
"\\mbffrakK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120182")
, (Text
"\\mbffrakL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120183")
, (Text
"\\mbffrakM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120184")
, (Text
"\\mbffrakN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120185")
, (Text
"\\mbffrakO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120186")
, (Text
"\\mbffrakP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120187")
, (Text
"\\mbffrakQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120188")
, (Text
"\\mbffrakR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120189")
, (Text
"\\mbffrakS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120190")
, (Text
"\\mbffrakT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120191")
, (Text
"\\mbffrakU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120192")
, (Text
"\\mbffrakV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120193")
, (Text
"\\mbffrakW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120194")
, (Text
"\\mbffrakX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120195")
, (Text
"\\mbffrakY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120196")
, (Text
"\\mbffrakZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120197")
, (Text
"\\mbffraka",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120198")
, (Text
"\\mbffrakb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120199")
, (Text
"\\mbffrakc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120200")
, (Text
"\\mbffrakd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120201")
, (Text
"\\mbffrake",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120202")
, (Text
"\\mbffrakf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120203")
, (Text
"\\mbffrakg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120204")
, (Text
"\\mbffrakh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120205")
, (Text
"\\mbffraki",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120206")
, (Text
"\\mbffrakj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120207")
, (Text
"\\mbffrakk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120208")
, (Text
"\\mbffrakl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120209")
, (Text
"\\mbffrakm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120210")
, (Text
"\\mbffrakn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120211")
, (Text
"\\mbffrako",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120212")
, (Text
"\\mbffrakp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120213")
, (Text
"\\mbffrakq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120214")
, (Text
"\\mbffrakr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120215")
, (Text
"\\mbffraks",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120216")
, (Text
"\\mbffrakt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120217")
, (Text
"\\mbffraku",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120218")
, (Text
"\\mbffrakv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120219")
, (Text
"\\mbffrakw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120220")
, (Text
"\\mbffrakx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120221")
, (Text
"\\mbffraky",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120222")
, (Text
"\\mbffrakz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120223")
, (Text
"\\mbfg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119840")
, (Text
"\\mbfgamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120516")
, (Text
"\\mbfh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119841")
, (Text
"\\mbfi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119842")
, (Text
"\\mbfiota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120522")
, (Text
"\\mbfitA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119912")
, (Text
"\\mbfitAlpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120604")
, (Text
"\\mbfitB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119913")
, (Text
"\\mbfitBeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120605")
, (Text
"\\mbfitC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119914")
, (Text
"\\mbfitChi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120626")
, (Text
"\\mbfitD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119915")
, (Text
"\\mbfitDelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120607")
, (Text
"\\mbfitE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119916")
, (Text
"\\mbfitEpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120608")
, (Text
"\\mbfitEta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120610")
, (Text
"\\mbfitF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119917")
, (Text
"\\mbfitG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119918")
, (Text
"\\mbfitGamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120606")
, (Text
"\\mbfitH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119919")
, (Text
"\\mbfitI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119920")
, (Text
"\\mbfitIota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120612")
, (Text
"\\mbfitJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119921")
, (Text
"\\mbfitK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119922")
, (Text
"\\mbfitKappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120613")
, (Text
"\\mbfitL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119923")
, (Text
"\\mbfitLambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120614")
, (Text
"\\mbfitM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119924")
, (Text
"\\mbfitMu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120615")
, (Text
"\\mbfitN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119925")
, (Text
"\\mbfitNu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120616")
, (Text
"\\mbfitO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119926")
, (Text
"\\mbfitOmega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120628")
, (Text
"\\mbfitOmicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120618")
, (Text
"\\mbfitP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119927")
, (Text
"\\mbfitPhi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120625")
, (Text
"\\mbfitPi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120619")
, (Text
"\\mbfitPsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120627")
, (Text
"\\mbfitQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119928")
, (Text
"\\mbfitR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119929")
, (Text
"\\mbfitRho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120620")
, (Text
"\\mbfitS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119930")
, (Text
"\\mbfitSigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120622")
, (Text
"\\mbfitT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119931")
, (Text
"\\mbfitTau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120623")
, (Text
"\\mbfitTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120611")
, (Text
"\\mbfitU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119932")
, (Text
"\\mbfitUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120624")
, (Text
"\\mbfitV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119933")
, (Text
"\\mbfitW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119934")
, (Text
"\\mbfitX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119935")
, (Text
"\\mbfitXi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120617")
, (Text
"\\mbfitY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119936")
, (Text
"\\mbfitZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119937")
, (Text
"\\mbfitZeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120609")
, (Text
"\\mbfita",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119938")
, (Text
"\\mbfitalpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120630")
, (Text
"\\mbfitb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119939")
, (Text
"\\mbfitbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120631")
, (Text
"\\mbfitc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119940")
, (Text
"\\mbfitchi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120652")
, (Text
"\\mbfitd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119941")
, (Text
"\\mbfitdelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120633")
, (Text
"\\mbfite",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119942")
, (Text
"\\mbfitepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120634")
, (Text
"\\mbfiteta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120636")
, (Text
"\\mbfitf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119943")
, (Text
"\\mbfitg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119944")
, (Text
"\\mbfitgamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120632")
, (Text
"\\mbfith",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119945")
, (Text
"\\mbfiti",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119946")
, (Text
"\\mbfitiota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120638")
, (Text
"\\mbfitj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119947")
, (Text
"\\mbfitk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119948")
, (Text
"\\mbfitkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120639")
, (Text
"\\mbfitl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119949")
, (Text
"\\mbfitlambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120640")
, (Text
"\\mbfitm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119950")
, (Text
"\\mbfitmu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120641")
, (Text
"\\mbfitn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119951")
, (Text
"\\mbfitnabla",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120629")
, (Text
"\\mbfitnu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120642")
, (Text
"\\mbfito",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119952")
, (Text
"\\mbfitomega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120654")
, (Text
"\\mbfitomicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120644")
, (Text
"\\mbfitp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119953")
, (Text
"\\mbfitpartial",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120655")
, (Text
"\\mbfitphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120651")
, (Text
"\\mbfitpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120645")
, (Text
"\\mbfitpsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120653")
, (Text
"\\mbfitq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119954")
, (Text
"\\mbfitr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119955")
, (Text
"\\mbfitrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120646")
, (Text
"\\mbfits",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119956")
, (Text
"\\mbfitsansA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120380")
, (Text
"\\mbfitsansAlpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120720")
, (Text
"\\mbfitsansB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120381")
, (Text
"\\mbfitsansBeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120721")
, (Text
"\\mbfitsansC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120382")
, (Text
"\\mbfitsansChi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120742")
, (Text
"\\mbfitsansD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120383")
, (Text
"\\mbfitsansDelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120723")
, (Text
"\\mbfitsansE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120384")
, (Text
"\\mbfitsansEpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120724")
, (Text
"\\mbfitsansEta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120726")
, (Text
"\\mbfitsansF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120385")
, (Text
"\\mbfitsansG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120386")
, (Text
"\\mbfitsansGamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120722")
, (Text
"\\mbfitsansH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120387")
, (Text
"\\mbfitsansI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120388")
, (Text
"\\mbfitsansIota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120728")
, (Text
"\\mbfitsansJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120389")
, (Text
"\\mbfitsansK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120390")
, (Text
"\\mbfitsansKappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120729")
, (Text
"\\mbfitsansL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120391")
, (Text
"\\mbfitsansLambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120730")
, (Text
"\\mbfitsansM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120392")
, (Text
"\\mbfitsansMu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120731")
, (Text
"\\mbfitsansN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120393")
, (Text
"\\mbfitsansNu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120732")
, (Text
"\\mbfitsansO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120394")
, (Text
"\\mbfitsansOmega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120744")
, (Text
"\\mbfitsansOmicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120734")
, (Text
"\\mbfitsansP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120395")
, (Text
"\\mbfitsansPhi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120741")
, (Text
"\\mbfitsansPi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120735")
, (Text
"\\mbfitsansPsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120743")
, (Text
"\\mbfitsansQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120396")
, (Text
"\\mbfitsansR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120397")
, (Text
"\\mbfitsansRho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120736")
, (Text
"\\mbfitsansS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120398")
, (Text
"\\mbfitsansSigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120738")
, (Text
"\\mbfitsansT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120399")
, (Text
"\\mbfitsansTau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120739")
, (Text
"\\mbfitsansTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120727")
, (Text
"\\mbfitsansU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120400")
, (Text
"\\mbfitsansUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120740")
, (Text
"\\mbfitsansV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120401")
, (Text
"\\mbfitsansW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120402")
, (Text
"\\mbfitsansX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120403")
, (Text
"\\mbfitsansXi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120733")
, (Text
"\\mbfitsansY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120404")
, (Text
"\\mbfitsansZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120405")
, (Text
"\\mbfitsansZeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120725")
, (Text
"\\mbfitsansa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120406")
, (Text
"\\mbfitsansalpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120746")
, (Text
"\\mbfitsansb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120407")
, (Text
"\\mbfitsansbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120747")
, (Text
"\\mbfitsansc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120408")
, (Text
"\\mbfitsanschi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120768")
, (Text
"\\mbfitsansd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120409")
, (Text
"\\mbfitsansdelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120749")
, (Text
"\\mbfitsanse",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120410")
, (Text
"\\mbfitsansepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120750")
, (Text
"\\mbfitsanseta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120752")
, (Text
"\\mbfitsansf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120411")
, (Text
"\\mbfitsansg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120412")
, (Text
"\\mbfitsansgamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120748")
, (Text
"\\mbfitsansh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120413")
, (Text
"\\mbfitsansi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120414")
, (Text
"\\mbfitsansiota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120754")
, (Text
"\\mbfitsansj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120415")
, (Text
"\\mbfitsansk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120416")
, (Text
"\\mbfitsanskappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120755")
, (Text
"\\mbfitsansl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120417")
, (Text
"\\mbfitsanslambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120756")
, (Text
"\\mbfitsansm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120418")
, (Text
"\\mbfitsansmu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120757")
, (Text
"\\mbfitsansn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120419")
, (Text
"\\mbfitsansnabla",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120745")
, (Text
"\\mbfitsansnu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120758")
, (Text
"\\mbfitsanso",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120420")
, (Text
"\\mbfitsansomega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120770")
, (Text
"\\mbfitsansomicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120760")
, (Text
"\\mbfitsansp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120421")
, (Text
"\\mbfitsanspartial",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120771")
, (Text
"\\mbfitsansphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120767")
, (Text
"\\mbfitsanspi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120761")
, (Text
"\\mbfitsanspsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120769")
, (Text
"\\mbfitsansq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120422")
, (Text
"\\mbfitsansr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120423")
, (Text
"\\mbfitsansrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120762")
, (Text
"\\mbfitsanss",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120424")
, (Text
"\\mbfitsanssigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120764")
, (Text
"\\mbfitsanst",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120425")
, (Text
"\\mbfitsanstau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120765")
, (Text
"\\mbfitsanstheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120753")
, (Text
"\\mbfitsansu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120426")
, (Text
"\\mbfitsansupsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120766")
, (Text
"\\mbfitsansv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120427")
, (Text
"\\mbfitsansvarTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120737")
, (Text
"\\mbfitsansvarepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120772")
, (Text
"\\mbfitsansvarkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120774")
, (Text
"\\mbfitsansvarphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120775")
, (Text
"\\mbfitsansvarpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120777")
, (Text
"\\mbfitsansvarrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120776")
, (Text
"\\mbfitsansvarsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120763")
, (Text
"\\mbfitsansvartheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120773")
, (Text
"\\mbfitsansw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120428")
, (Text
"\\mbfitsansx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120429")
, (Text
"\\mbfitsansxi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120759")
, (Text
"\\mbfitsansy",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120430")
, (Text
"\\mbfitsansz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120431")
, (Text
"\\mbfitsanszeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120751")
, (Text
"\\mbfitsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120648")
, (Text
"\\mbfitt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119957")
, (Text
"\\mbfittau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120649")
, (Text
"\\mbfittheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120637")
, (Text
"\\mbfitu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119958")
, (Text
"\\mbfitupsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120650")
, (Text
"\\mbfitv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119959")
, (Text
"\\mbfitvarTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120621")
, (Text
"\\mbfitvarepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120656")
, (Text
"\\mbfitvarkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120658")
, (Text
"\\mbfitvarphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120659")
, (Text
"\\mbfitvarpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120661")
, (Text
"\\mbfitvarrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120660")
, (Text
"\\mbfitvarsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120647")
, (Text
"\\mbfitvartheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120657")
, (Text
"\\mbfitw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119960")
, (Text
"\\mbfitx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119961")
, (Text
"\\mbfitxi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120643")
, (Text
"\\mbfity",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119962")
, (Text
"\\mbfitz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119963")
, (Text
"\\mbfitzeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120635")
, (Text
"\\mbfj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119843")
, (Text
"\\mbfk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119844")
, (Text
"\\mbfkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120523")
, (Text
"\\mbfl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119845")
, (Text
"\\mbflambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120524")
, (Text
"\\mbfm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119846")
, (Text
"\\mbfmu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120525")
, (Text
"\\mbfn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119847")
, (Text
"\\mbfnabla",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120513")
, (Text
"\\mbfnu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120526")
, (Text
"\\mbfo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119848")
, (Text
"\\mbfomega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120538")
, (Text
"\\mbfomicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120528")
, (Text
"\\mbfp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119849")
, (Text
"\\mbfpartial",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120539")
, (Text
"\\mbfphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120543")
, (Text
"\\mbfpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120529")
, (Text
"\\mbfpsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120537")
, (Text
"\\mbfq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119850")
, (Text
"\\mbfr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119851")
, (Text
"\\mbfrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120530")
, (Text
"\\mbfs",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119852")
, (Text
"\\mbfsansA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120276")
, (Text
"\\mbfsansAlpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120662")
, (Text
"\\mbfsansB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120277")
, (Text
"\\mbfsansBeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120663")
, (Text
"\\mbfsansC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120278")
, (Text
"\\mbfsansChi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120684")
, (Text
"\\mbfsansD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120279")
, (Text
"\\mbfsansDelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120665")
, (Text
"\\mbfsansE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120280")
, (Text
"\\mbfsansEpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120666")
, (Text
"\\mbfsansEta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120668")
, (Text
"\\mbfsansF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120281")
, (Text
"\\mbfsansG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120282")
, (Text
"\\mbfsansGamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120664")
, (Text
"\\mbfsansH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120283")
, (Text
"\\mbfsansI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120284")
, (Text
"\\mbfsansIota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120670")
, (Text
"\\mbfsansJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120285")
, (Text
"\\mbfsansK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120286")
, (Text
"\\mbfsansKappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120671")
, (Text
"\\mbfsansL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120287")
, (Text
"\\mbfsansLambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120672")
, (Text
"\\mbfsansM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120288")
, (Text
"\\mbfsansMu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120673")
, (Text
"\\mbfsansN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120289")
, (Text
"\\mbfsansNu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120674")
, (Text
"\\mbfsansO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120290")
, (Text
"\\mbfsansOmega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120686")
, (Text
"\\mbfsansOmicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120676")
, (Text
"\\mbfsansP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120291")
, (Text
"\\mbfsansPhi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120683")
, (Text
"\\mbfsansPi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120677")
, (Text
"\\mbfsansPsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120685")
, (Text
"\\mbfsansQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120292")
, (Text
"\\mbfsansR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120293")
, (Text
"\\mbfsansRho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120678")
, (Text
"\\mbfsansS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120294")
, (Text
"\\mbfsansSigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120680")
, (Text
"\\mbfsansT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120295")
, (Text
"\\mbfsansTau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120681")
, (Text
"\\mbfsansTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120669")
, (Text
"\\mbfsansU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120296")
, (Text
"\\mbfsansUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120682")
, (Text
"\\mbfsansV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120297")
, (Text
"\\mbfsansW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120298")
, (Text
"\\mbfsansX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120299")
, (Text
"\\mbfsansXi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120675")
, (Text
"\\mbfsansY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120300")
, (Text
"\\mbfsansZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120301")
, (Text
"\\mbfsansZeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120667")
, (Text
"\\mbfsansa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120302")
, (Text
"\\mbfsansalpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120688")
, (Text
"\\mbfsansb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120303")
, (Text
"\\mbfsansbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120689")
, (Text
"\\mbfsansc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120304")
, (Text
"\\mbfsanschi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120710")
, (Text
"\\mbfsansd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120305")
, (Text
"\\mbfsansdelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120691")
, (Text
"\\mbfsanse",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120306")
, (Text
"\\mbfsanseight",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120820")
, (Text
"\\mbfsansepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120692")
, (Text
"\\mbfsanseta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120694")
, (Text
"\\mbfsansf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120307")
, (Text
"\\mbfsansfive",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120817")
, (Text
"\\mbfsansfour",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120816")
, (Text
"\\mbfsansg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120308")
, (Text
"\\mbfsansgamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120690")
, (Text
"\\mbfsansh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120309")
, (Text
"\\mbfsansi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120310")
, (Text
"\\mbfsansiota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120696")
, (Text
"\\mbfsansj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120311")
, (Text
"\\mbfsansk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120312")
, (Text
"\\mbfsanskappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120697")
, (Text
"\\mbfsansl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120313")
, (Text
"\\mbfsanslambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120698")
, (Text
"\\mbfsansm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120314")
, (Text
"\\mbfsansmu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120699")
, (Text
"\\mbfsansn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120315")
, (Text
"\\mbfsansnabla",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120687")
, (Text
"\\mbfsansnine",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120821")
, (Text
"\\mbfsansnu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120700")
, (Text
"\\mbfsanso",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120316")
, (Text
"\\mbfsansomega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120712")
, (Text
"\\mbfsansomicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120702")
, (Text
"\\mbfsansone",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120813")
, (Text
"\\mbfsansp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120317")
, (Text
"\\mbfsanspartial",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120713")
, (Text
"\\mbfsansphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120709")
, (Text
"\\mbfsanspi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120703")
, (Text
"\\mbfsanspsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120711")
, (Text
"\\mbfsansq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120318")
, (Text
"\\mbfsansr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120319")
, (Text
"\\mbfsansrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120704")
, (Text
"\\mbfsanss",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120320")
, (Text
"\\mbfsansseven",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120819")
, (Text
"\\mbfsanssigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120706")
, (Text
"\\mbfsanssix",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120818")
, (Text
"\\mbfsanst",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120321")
, (Text
"\\mbfsanstau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120707")
, (Text
"\\mbfsanstheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120695")
, (Text
"\\mbfsansthree",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120815")
, (Text
"\\mbfsanstwo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120814")
, (Text
"\\mbfsansu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120322")
, (Text
"\\mbfsansupsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120708")
, (Text
"\\mbfsansv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120323")
, (Text
"\\mbfsansvarTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120679")
, (Text
"\\mbfsansvarepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120714")
, (Text
"\\mbfsansvarkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120716")
, (Text
"\\mbfsansvarphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120717")
, (Text
"\\mbfsansvarpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120719")
, (Text
"\\mbfsansvarrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120718")
, (Text
"\\mbfsansvarsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120705")
, (Text
"\\mbfsansvartheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120715")
, (Text
"\\mbfsansw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120324")
, (Text
"\\mbfsansx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120325")
, (Text
"\\mbfsansxi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120701")
, (Text
"\\mbfsansy",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120326")
, (Text
"\\mbfsansz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120327")
, (Text
"\\mbfsanszero",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120812")
, (Text
"\\mbfsanszeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120693")
, (Text
"\\mbfscrA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120016")
, (Text
"\\mbfscrB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120017")
, (Text
"\\mbfscrC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120018")
, (Text
"\\mbfscrD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120019")
, (Text
"\\mbfscrE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120020")
, (Text
"\\mbfscrF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120021")
, (Text
"\\mbfscrG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120022")
, (Text
"\\mbfscrH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120023")
, (Text
"\\mbfscrI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120024")
, (Text
"\\mbfscrJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120025")
, (Text
"\\mbfscrK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120026")
, (Text
"\\mbfscrL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120027")
, (Text
"\\mbfscrM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120028")
, (Text
"\\mbfscrN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120029")
, (Text
"\\mbfscrO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120030")
, (Text
"\\mbfscrP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120031")
, (Text
"\\mbfscrQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120032")
, (Text
"\\mbfscrR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120033")
, (Text
"\\mbfscrS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120034")
, (Text
"\\mbfscrT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120035")
, (Text
"\\mbfscrU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120036")
, (Text
"\\mbfscrV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120037")
, (Text
"\\mbfscrW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120038")
, (Text
"\\mbfscrX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120039")
, (Text
"\\mbfscrY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120040")
, (Text
"\\mbfscrZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120041")
, (Text
"\\mbfscra",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120042")
, (Text
"\\mbfscrb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120043")
, (Text
"\\mbfscrc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120044")
, (Text
"\\mbfscrd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120045")
, (Text
"\\mbfscre",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120046")
, (Text
"\\mbfscrf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120047")
, (Text
"\\mbfscrg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120048")
, (Text
"\\mbfscrh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120049")
, (Text
"\\mbfscri",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120050")
, (Text
"\\mbfscrj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120051")
, (Text
"\\mbfscrk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120052")
, (Text
"\\mbfscrl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120053")
, (Text
"\\mbfscrm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120054")
, (Text
"\\mbfscrn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120055")
, (Text
"\\mbfscro",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120056")
, (Text
"\\mbfscrp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120057")
, (Text
"\\mbfscrq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120058")
, (Text
"\\mbfscrr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120059")
, (Text
"\\mbfscrs",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120060")
, (Text
"\\mbfscrt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120061")
, (Text
"\\mbfscru",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120062")
, (Text
"\\mbfscrv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120063")
, (Text
"\\mbfscrw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120064")
, (Text
"\\mbfscrx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120065")
, (Text
"\\mbfscry",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120066")
, (Text
"\\mbfscrz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120067")
, (Text
"\\mbfsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120532")
, (Text
"\\mbft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119853")
, (Text
"\\mbftau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120533")
, (Text
"\\mbftheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120521")
, (Text
"\\mbfu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119854")
, (Text
"\\mbfupsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120534")
, (Text
"\\mbfv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119855")
, (Text
"\\mbfvarTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120505")
, (Text
"\\mbfvarepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120540")
, (Text
"\\mbfvarkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120542")
, (Text
"\\mbfvarphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120535")
, (Text
"\\mbfvarpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120545")
, (Text
"\\mbfvarrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120544")
, (Text
"\\mbfvarsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120531")
, (Text
"\\mbfvartheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120541")
, (Text
"\\mbfw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119856")
, (Text
"\\mbfx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119857")
, (Text
"\\mbfxi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120527")
, (Text
"\\mbfy",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119858")
, (Text
"\\mbfz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119859")
, (Text
"\\mbfzeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120519")
, (Text
"\\mdblkcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9899")
, (Text
"\\mdblkdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11045")
, (Text
"\\mdblklozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11047")
, (Text
"\\mdblksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9724")
, (Text
"\\mdlgblkcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9679")
, (Text
"\\mdlgblkdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9670")
, (Text
"\\mdlgblklozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10731")
, (Text
"\\mdlgblksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9632")
, (Text
"\\mdlgwhtcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9675")
, (Text
"\\mdlgwhtdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9671")
, (Text
"\\mdlgwhtlozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9674")
, (Text
"\\mdlgwhtsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9633")
, (Text
"\\mdsmblkcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10625")
, (Text
"\\mdsmblksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9726")
, (Text
"\\mdsmwhtcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9900")
, (Text
"\\mdsmwhtsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9725")
, (Text
"\\mdwhtcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9898")
, (Text
"\\mdwhtdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11046")
, (Text
"\\mdwhtlozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11048")
, (Text
"\\mdwhtsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9723")
, (Text
"\\measangledltosw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10671")
, (Text
"\\measangledrtose",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10670")
, (Text
"\\measangleldtosw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10667")
, (Text
"\\measanglelutonw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10665")
, (Text
"\\measanglerdtose",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10666")
, (Text
"\\measanglerutone",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10664")
, (Text
"\\measangleultonw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10669")
, (Text
"\\measangleurtone",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10668")
, (Text
"\\measeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8798")
, (Text
"\\measuredangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8737")
, (Text
"\\measuredangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10651")
, (Text
"\\measuredrightangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8894")
, (Text
"\\medblackstar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11089")
, (Text
"\\medbullet",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9899")
, (Text
"\\medcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9898")
, (Text
"\\medspace",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8287")
, (Text
"\\medwhitestar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11088")
, (Text
"\\mercury",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9791")
, (Text
"\\mfrakA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120068")
, (Text
"\\mfrakB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120069")
, (Text
"\\mfrakC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8493")
, (Text
"\\mfrakD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120071")
, (Text
"\\mfrakE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120072")
, (Text
"\\mfrakF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120073")
, (Text
"\\mfrakG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120074")
, (Text
"\\mfrakH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8460")
, (Text
"\\mfrakJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120077")
, (Text
"\\mfrakK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120078")
, (Text
"\\mfrakL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120079")
, (Text
"\\mfrakM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120080")
, (Text
"\\mfrakN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120081")
, (Text
"\\mfrakO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120082")
, (Text
"\\mfrakP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120083")
, (Text
"\\mfrakQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120084")
, (Text
"\\mfrakS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120086")
, (Text
"\\mfrakT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120087")
, (Text
"\\mfrakU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120088")
, (Text
"\\mfrakV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120089")
, (Text
"\\mfrakW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120090")
, (Text
"\\mfrakX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120091")
, (Text
"\\mfrakY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120092")
, (Text
"\\mfrakZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8488")
, (Text
"\\mfraka",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120094")
, (Text
"\\mfrakb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120095")
, (Text
"\\mfrakc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120096")
, (Text
"\\mfrakd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120097")
, (Text
"\\mfrake",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120098")
, (Text
"\\mfrakf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120099")
, (Text
"\\mfrakg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120100")
, (Text
"\\mfrakh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120101")
, (Text
"\\mfraki",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120102")
, (Text
"\\mfrakj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120103")
, (Text
"\\mfrakk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120104")
, (Text
"\\mfrakl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120105")
, (Text
"\\mfrakm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120106")
, (Text
"\\mfrakn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120107")
, (Text
"\\mfrako",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120108")
, (Text
"\\mfrakp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120109")
, (Text
"\\mfrakq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120110")
, (Text
"\\mfrakr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120111")
, (Text
"\\mfraks",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120112")
, (Text
"\\mfrakt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120113")
, (Text
"\\mfraku",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120114")
, (Text
"\\mfrakv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120115")
, (Text
"\\mfrakw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120116")
, (Text
"\\mfrakx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120117")
, (Text
"\\mfraky",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120118")
, (Text
"\\mfrakz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120119")
, (Text
"\\mho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8487")
, (Text
"\\midbarvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10845")
, (Text
"\\midbarwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10844")
, (Text
"\\midcir",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10992")
, (Text
"\\minus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8722")
, (Text
"\\minusdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10794")
, (Text
"\\minusfdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10795")
, (Text
"\\minusrdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10796")
, (Text
"\\mitA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119860")
, (Text
"\\mitAlpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120546")
, (Text
"\\mitB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119861")
, (Text
"\\mitBbbD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8517")
, (Text
"\\mitBbbd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8518")
, (Text
"\\mitBbbe",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8519")
, (Text
"\\mitBbbi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8520")
, (Text
"\\mitBbbj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8521")
, (Text
"\\mitBeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120547")
, (Text
"\\mitC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119862")
, (Text
"\\mitChi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120568")
, (Text
"\\mitD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119863")
, (Text
"\\mitDelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120549")
, (Text
"\\mitE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119864")
, (Text
"\\mitEpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120550")
, (Text
"\\mitEta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120552")
, (Text
"\\mitF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119865")
, (Text
"\\mitG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119866")
, (Text
"\\mitGamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120548")
, (Text
"\\mitH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119867")
, (Text
"\\mitI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119868")
, (Text
"\\mitIota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120554")
, (Text
"\\mitJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119869")
, (Text
"\\mitK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119870")
, (Text
"\\mitKappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120555")
, (Text
"\\mitL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119871")
, (Text
"\\mitLambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120556")
, (Text
"\\mitM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119872")
, (Text
"\\mitMu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120557")
, (Text
"\\mitN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119873")
, (Text
"\\mitNu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120558")
, (Text
"\\mitO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119874")
, (Text
"\\mitOmega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120570")
, (Text
"\\mitOmicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120560")
, (Text
"\\mitP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119875")
, (Text
"\\mitPhi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120567")
, (Text
"\\mitPi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120561")
, (Text
"\\mitPsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120569")
, (Text
"\\mitQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119876")
, (Text
"\\mitR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119877")
, (Text
"\\mitRho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120562")
, (Text
"\\mitS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119878")
, (Text
"\\mitSigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120564")
, (Text
"\\mitT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119879")
, (Text
"\\mitTau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120565")
, (Text
"\\mitTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120553")
, (Text
"\\mitU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119880")
, (Text
"\\mitUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120566")
, (Text
"\\mitV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119881")
, (Text
"\\mitW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119882")
, (Text
"\\mitX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119883")
, (Text
"\\mitXi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120559")
, (Text
"\\mitY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119884")
, (Text
"\\mitZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119885")
, (Text
"\\mitZeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120551")
, (Text
"\\mita",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119886")
, (Text
"\\mitalpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120572")
, (Text
"\\mitb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119887")
, (Text
"\\mitbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120573")
, (Text
"\\mitc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119888")
, (Text
"\\mitchi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120594")
, (Text
"\\mitd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119889")
, (Text
"\\mitdelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120575")
, (Text
"\\mite",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119890")
, (Text
"\\mitepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120576")
, (Text
"\\miteta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120578")
, (Text
"\\mitf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119891")
, (Text
"\\mitg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119892")
, (Text
"\\mitgamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120574")
, (Text
"\\miti",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119894")
, (Text
"\\mitiota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120580")
, (Text
"\\mitj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119895")
, (Text
"\\mitk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119896")
, (Text
"\\mitkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120581")
, (Text
"\\mitl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119897")
, (Text
"\\mitlambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120582")
, (Text
"\\mitm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119898")
, (Text
"\\mitmu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120583")
, (Text
"\\mitn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119899")
, (Text
"\\mitnabla",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120571")
, (Text
"\\mitnu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120584")
, (Text
"\\mito",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119900")
, (Text
"\\mitomega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120596")
, (Text
"\\mitomicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120586")
, (Text
"\\mitp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119901")
, (Text
"\\mitpartial",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120597")
, (Text
"\\mitphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120593")
, (Text
"\\mitpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120587")
, (Text
"\\mitpsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120595")
, (Text
"\\mitq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119902")
, (Text
"\\mitr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119903")
, (Text
"\\mitrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120588")
, (Text
"\\mits",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119904")
, (Text
"\\mitsansA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120328")
, (Text
"\\mitsansB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120329")
, (Text
"\\mitsansC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120330")
, (Text
"\\mitsansD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120331")
, (Text
"\\mitsansE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120332")
, (Text
"\\mitsansF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120333")
, (Text
"\\mitsansG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120334")
, (Text
"\\mitsansH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120335")
, (Text
"\\mitsansI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120336")
, (Text
"\\mitsansJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120337")
, (Text
"\\mitsansK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120338")
, (Text
"\\mitsansL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120339")
, (Text
"\\mitsansM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120340")
, (Text
"\\mitsansN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120341")
, (Text
"\\mitsansO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120342")
, (Text
"\\mitsansP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120343")
, (Text
"\\mitsansQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120344")
, (Text
"\\mitsansR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120345")
, (Text
"\\mitsansS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120346")
, (Text
"\\mitsansT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120347")
, (Text
"\\mitsansU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120348")
, (Text
"\\mitsansV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120349")
, (Text
"\\mitsansW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120350")
, (Text
"\\mitsansX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120351")
, (Text
"\\mitsansY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120352")
, (Text
"\\mitsansZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120353")
, (Text
"\\mitsansa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120354")
, (Text
"\\mitsansb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120355")
, (Text
"\\mitsansc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120356")
, (Text
"\\mitsansd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120357")
, (Text
"\\mitsanse",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120358")
, (Text
"\\mitsansf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120359")
, (Text
"\\mitsansg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120360")
, (Text
"\\mitsansh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120361")
, (Text
"\\mitsansi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120362")
, (Text
"\\mitsansj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120363")
, (Text
"\\mitsansk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120364")
, (Text
"\\mitsansl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120365")
, (Text
"\\mitsansm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120366")
, (Text
"\\mitsansn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120367")
, (Text
"\\mitsanso",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120368")
, (Text
"\\mitsansp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120369")
, (Text
"\\mitsansq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120370")
, (Text
"\\mitsansr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120371")
, (Text
"\\mitsanss",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120372")
, (Text
"\\mitsanst",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120373")
, (Text
"\\mitsansu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120374")
, (Text
"\\mitsansv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120375")
, (Text
"\\mitsansw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120376")
, (Text
"\\mitsansx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120377")
, (Text
"\\mitsansy",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120378")
, (Text
"\\mitsansz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120379")
, (Text
"\\mitsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120590")
, (Text
"\\mitt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119905")
, (Text
"\\mittau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120591")
, (Text
"\\mittheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120579")
, (Text
"\\mitu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119906")
, (Text
"\\mitupsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120592")
, (Text
"\\mitv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119907")
, (Text
"\\mitvarTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120563")
, (Text
"\\mitvarepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120598")
, (Text
"\\mitvarkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120600")
, (Text
"\\mitvarphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120601")
, (Text
"\\mitvarpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120603")
, (Text
"\\mitvarrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120602")
, (Text
"\\mitvarsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120589")
, (Text
"\\mitvartheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120599")
, (Text
"\\mitw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119908")
, (Text
"\\mitx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119909")
, (Text
"\\mitxi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120585")
, (Text
"\\mity",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119910")
, (Text
"\\mitz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119911")
, (Text
"\\mitzeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120577")
, (Text
"\\mlcp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10971")
, (Text
"\\modtwosum",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10762")
, (Text
"\\msansA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120224")
, (Text
"\\msansB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120225")
, (Text
"\\msansC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120226")
, (Text
"\\msansD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120227")
, (Text
"\\msansE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120228")
, (Text
"\\msansF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120229")
, (Text
"\\msansG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120230")
, (Text
"\\msansH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120231")
, (Text
"\\msansI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120232")
, (Text
"\\msansJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120233")
, (Text
"\\msansK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120234")
, (Text
"\\msansL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120235")
, (Text
"\\msansM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120236")
, (Text
"\\msansN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120237")
, (Text
"\\msansO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120238")
, (Text
"\\msansP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120239")
, (Text
"\\msansQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120240")
, (Text
"\\msansR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120241")
, (Text
"\\msansS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120242")
, (Text
"\\msansT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120243")
, (Text
"\\msansU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120244")
, (Text
"\\msansV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120245")
, (Text
"\\msansW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120246")
, (Text
"\\msansX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120247")
, (Text
"\\msansY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120248")
, (Text
"\\msansZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120249")
, (Text
"\\msansa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120250")
, (Text
"\\msansb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120251")
, (Text
"\\msansc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120252")
, (Text
"\\msansd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120253")
, (Text
"\\msanse",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120254")
, (Text
"\\msanseight",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120810")
, (Text
"\\msansf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120255")
, (Text
"\\msansfive",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120807")
, (Text
"\\msansfour",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120806")
, (Text
"\\msansg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120256")
, (Text
"\\msansh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120257")
, (Text
"\\msansi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120258")
, (Text
"\\msansj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120259")
, (Text
"\\msansk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120260")
, (Text
"\\msansl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120261")
, (Text
"\\msansm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120262")
, (Text
"\\msansn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120263")
, (Text
"\\msansnine",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120811")
, (Text
"\\msanso",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120264")
, (Text
"\\msansone",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120803")
, (Text
"\\msansp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120265")
, (Text
"\\msansq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120266")
, (Text
"\\msansr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120267")
, (Text
"\\msanss",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120268")
, (Text
"\\msansseven",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120809")
, (Text
"\\msanssix",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120808")
, (Text
"\\msanst",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120269")
, (Text
"\\msansthree",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120805")
, (Text
"\\msanstwo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120804")
, (Text
"\\msansu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120270")
, (Text
"\\msansv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120271")
, (Text
"\\msansw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120272")
, (Text
"\\msansx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120273")
, (Text
"\\msansy",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120274")
, (Text
"\\msansz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120275")
, (Text
"\\msanszero",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120802")
, (Text
"\\mscrA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119964")
, (Text
"\\mscrB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8492")
, (Text
"\\mscrC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119966")
, (Text
"\\mscrD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119967")
, (Text
"\\mscrE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8496")
, (Text
"\\mscrF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8497")
, (Text
"\\mscrG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119970")
, (Text
"\\mscrH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8459")
, (Text
"\\mscrI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8464")
, (Text
"\\mscrJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119973")
, (Text
"\\mscrK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119974")
, (Text
"\\mscrL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8466")
, (Text
"\\mscrM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8499")
, (Text
"\\mscrN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119977")
, (Text
"\\mscrO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119978")
, (Text
"\\mscrP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119979")
, (Text
"\\mscrQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119980")
, (Text
"\\mscrR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8475")
, (Text
"\\mscrS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119982")
, (Text
"\\mscrT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119983")
, (Text
"\\mscrU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119984")
, (Text
"\\mscrV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119985")
, (Text
"\\mscrW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119986")
, (Text
"\\mscrX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119987")
, (Text
"\\mscrY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119988")
, (Text
"\\mscrZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119989")
, (Text
"\\mscra",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119990")
, (Text
"\\mscrb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119991")
, (Text
"\\mscrc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119992")
, (Text
"\\mscrd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119993")
, (Text
"\\mscre",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8495")
, (Text
"\\mscrf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119995")
, (Text
"\\mscrg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8458")
, (Text
"\\mscrh",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119997")
, (Text
"\\mscri",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119998")
, (Text
"\\mscrj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\119999")
, (Text
"\\mscrk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120000")
, (Text
"\\mscrl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120001")
, (Text
"\\mscrm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120002")
, (Text
"\\mscrn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120003")
, (Text
"\\mscro",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8500")
, (Text
"\\mscrp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120005")
, (Text
"\\mscrq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120006")
, (Text
"\\mscrr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120007")
, (Text
"\\mscrs",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120008")
, (Text
"\\mscrt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120009")
, (Text
"\\mscru",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120010")
, (Text
"\\mscrv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120011")
, (Text
"\\mscrw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120012")
, (Text
"\\mscrx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120013")
, (Text
"\\mscry",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120014")
, (Text
"\\mscrz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120015")
, (Text
"\\mttA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120432")
, (Text
"\\mttB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120433")
, (Text
"\\mttC",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120434")
, (Text
"\\mttD",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120435")
, (Text
"\\mttE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120436")
, (Text
"\\mttF",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120437")
, (Text
"\\mttG",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120438")
, (Text
"\\mttH",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120439")
, (Text
"\\mttI",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120440")
, (Text
"\\mttJ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120441")
, (Text
"\\mttK",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120442")
, (Text
"\\mttL",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120443")
, (Text
"\\mttM",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120444")
, (Text
"\\mttN",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120445")
, (Text
"\\mttO",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120446")
, (Text
"\\mttP",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120447")
, (Text
"\\mttQ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120448")
, (Text
"\\mttR",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120449")
, (Text
"\\mttS",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120450")
, (Text
"\\mttT",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120451")
, (Text
"\\mttU",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120452")
, (Text
"\\mttV",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120453")
, (Text
"\\mttW",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120454")
, (Text
"\\mttX",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120455")
, (Text
"\\mttY",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120456")
, (Text
"\\mttZ",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120457")
, (Text
"\\mtta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120458")
, (Text
"\\mttb",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120459")
, (Text
"\\mttc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120460")
, (Text
"\\mttd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120461")
, (Text
"\\mtte",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120462")
, (Text
"\\mtteight",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120830")
, (Text
"\\mttf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120463")
, (Text
"\\mttfive",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120827")
, (Text
"\\mttfour",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120826")
, (Text
"\\mttg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120464")
, (Text
"\\mtth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120465")
, (Text
"\\mtti",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120466")
, (Text
"\\mttj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120467")
, (Text
"\\mttk",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120468")
, (Text
"\\mttl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120469")
, (Text
"\\mttm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120470")
, (Text
"\\mttn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120471")
, (Text
"\\mttnine",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120831")
, (Text
"\\mtto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120472")
, (Text
"\\mttone",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120823")
, (Text
"\\mttp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120473")
, (Text
"\\mttq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120474")
, (Text
"\\mttr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120475")
, (Text
"\\mtts",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120476")
, (Text
"\\mttseven",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120829")
, (Text
"\\mttsix",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120828")
, (Text
"\\mttt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120477")
, (Text
"\\mttthree",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120825")
, (Text
"\\mtttwo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120824")
, (Text
"\\mttu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120478")
, (Text
"\\mttv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120479")
, (Text
"\\mttw",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120480")
, (Text
"\\mttx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120481")
, (Text
"\\mtty",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120482")
, (Text
"\\mttz",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120483")
, (Text
"\\mttzero",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\120822")
, (Text
"\\multimap",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8888")
, (Text
"\\multimapboth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10719")
, (Text
"\\multimapdotbothA",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8886")
, (Text
"\\multimapdotbothB",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8887")
, (Text
"\\multimapinv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10204")
, (Text
"\\nHdownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8671")
, (Text
"\\nHuparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8670")
, (Text
"\\nLeftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8653")
, (Text
"\\nLeftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8654")
, (Text
"\\nRightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8655")
, (Text
"\\nVDash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8879")
, (Text
"\\nVdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8878")
, (Text
"\\nVleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8698")
, (Text
"\\nVleftarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11066")
, (Text
"\\nVleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8700")
, (Text
"\\nVrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8699")
, (Text
"\\nVrightarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10517")
, (Text
"\\nVtwoheadleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11061")
, (Text
"\\nVtwoheadleftarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11069")
, (Text
"\\nVtwoheadrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10497")
, (Text
"\\nVtwoheadrightarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10520")
, (Text
"\\napprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8777")
, (Text
"\\nasymp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8813")
, (Text
"\\natural",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9838")
, (Text
"\\ncong",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8775")
, (Text
"\\ndres",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10852")
, (Text
"\\neovnwarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10545")
, (Text
"\\neovsearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10542")
, (Text
"\\neptune",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9798")
, (Text
"\\nequiv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8802")
, (Text
"\\neswarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10530")
, (Text
"\\neuter",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9906")
, (Text
"\\nexi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8708")
, (Text
"\\nexists",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8708")
, (Text
"\\ngeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8817")
, (Text
"\\ngeqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8817")
, (Text
"\\ngtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8815")
, (Text
"\\ngtrless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8825")
, (Text
"\\ngtrsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8821")
, (Text
"\\nhVvert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10997")
, (Text
"\\nhpar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10994")
, (Text
"\\nin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8713")
, (Text
"\\niobar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8958")
, (Text
"\\nis",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8956")
, (Text
"\\nisd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8954")
, (Text
"\\nleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8602")
, (Text
"\\nleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8622")
, (Text
"\\nleq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8816")
, (Text
"\\nleqslant",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8816")
, (Text
"\\nless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8814")
, (Text
"\\nlessgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8824")
, (Text
"\\nlesssim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8820")
, (Text
"\\nmid",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8740")
, (Text
"\\nni",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8716")
, (Text
"\\not",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\824")
, (Text
"\\notasymp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8813")
, (Text
"\\notbackslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9024")
, (Text
"\\notni",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8716")
, (Text
"\\notslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\9023")
, (Text
"\\nparallel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8742")
, (Text
"\\npolint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10772")
, (Text
"\\nprec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8832")
, (Text
"\\npreccurlyeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8928")
, (Text
"\\npreceq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8928")
, (Text
"\\nrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8603")
, (Text
"\\nrres",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10853")
, (Text
"\\nsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8769")
, (Text
"\\nsime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8772")
, (Text
"\\nsimeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8772")
, (Text
"\\nsqsubseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8930")
, (Text
"\\nsqsupseteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8931")
, (Text
"\\nsucc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8833")
, (Text
"\\nsucccurlyeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8929")
, (Text
"\\nsucceq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8929")
, (Text
"\\ntriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8938")
, (Text
"\\ntrianglelefteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8940")
, (Text
"\\ntriangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8939")
, (Text
"\\ntrianglerighteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8941")
, (Text
"\\nunlhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8940")
, (Text
"\\nunrhd",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8941")
, (Text
"\\nvDash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8877")
, (Text
"\\nvLeftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10498")
, (Text
"\\nvLeftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10500")
, (Text
"\\nvRightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10499")
, (Text
"\\nvdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8876")
, (Text
"\\nvinfty",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10718")
, (Text
"\\nvleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8695")
, (Text
"\\nvleftarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11065")
, (Text
"\\nvleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8697")
, (Text
"\\nvrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8696")
, (Text
"\\nvrightarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10516")
, (Text
"\\nvtwoheadleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11060")
, (Text
"\\nvtwoheadleftarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11068")
, (Text
"\\nvtwoheadrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10496")
, (Text
"\\nvtwoheadrightarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10519")
, (Text
"\\nwovnearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10546")
, (Text
"\\nwsearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10529")
, (Text
"\\obar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9021")
, (Text
"\\obot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10682")
, (Text
"\\obrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9184")
, (Text
"\\obslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10680")
, (Text
"\\ocirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\778")
, (Text
"\\ocommatopright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\789")
, (Text
"\\octothorpe",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"#")
, (Text
"\\odiv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10808")
, (Text
"\\odotslashdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10684")
, (Text
"\\ogreaterthan",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10689")
, (Text
"\\oiiint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8752")
, (Text
"\\oiint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8751")
, (Text
"\\ointctrclockwise",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8755")
, (Text
"\\olcross",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10683")
, (Text
"\\olessthan",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10688")
, (Text
"\\operp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10681")
, (Text
"\\opluslhrim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10797")
, (Text
"\\oplusrhrim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10798")
, (Text
"\\origof",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8886")
, (Text
"\\otimeshat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10806")
, (Text
"\\otimeslhrim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10804")
, (Text
"\\otimesrhrim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10805")
, (Text
"\\oturnedcomma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\786")
, (Text
"\\overbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\175")
, (Text
"\\overbrace",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TOver Text
"\9182")
, (Text
"\\overbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TOver Text
"\9140")
, (Text
"\\overleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8406")
, (Text
"\\overrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8407")
, (Text
"\\overleftrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8417")
, (Text
"\\overline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TOver Text
"\175")
, (Text
"\\overparen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TOver Text
"\9180")
, (Text
"\\ovhook",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\777")
, (Text
"\\parallelogram",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9649")
, (Text
"\\parallelogramblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9648")
, (Text
"\\parsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10995")
, (Text
"\\partialmeetcontraction",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10915")
, (Text
"\\partialup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8706")
, (Text
"\\pencil",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9998")
, (Text
"\\pentagon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11040")
, (Text
"\\pentagonblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11039")
, (Text
"\\percent",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"%")
, (Text
"\\period",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
".")
, (Text
"\\perps",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10977")
, (Text
"\\pfun",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8696")
, (Text
"\\pinj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10516")
, (Text
"\\pisces",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9811")
, (Text
"\\pitchfork",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8916")
, (Text
"\\plus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"+")
, (Text
"\\plusdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10789")
, (Text
"\\pluseqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10866")
, (Text
"\\plushat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10787")
, (Text
"\\plussim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10790")
, (Text
"\\plussubtwo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10791")
, (Text
"\\plustrif",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10792")
, (Text
"\\pluto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9799")
, (Text
"\\pointint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10773")
, (Text
"\\pointright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9758")
, (Text
"\\postalmark",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\12306")
, (Text
"\\pounds",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\163")
, (Text
"\\precapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10935")
, (Text
"\\preccurlyeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8828")
, (Text
"\\preceqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10931")
, (Text
"\\precnapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10937")
, (Text
"\\precneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10929")
, (Text
"\\precneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10933")
, (Text
"\\precnsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8936")
, (Text
"\\precsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8830")
, (Text
"\\profline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8978")
, (Text
"\\profsurf",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8979")
, (Text
"\\project",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10785")
, (Text
"\\prurel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8880")
, (Text
"\\psur",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10496")
, (Text
"\\psurj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10496")
, (Text
"\\pullback",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10195")
, (Text
"\\pushout",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10196")
, (Text
"\\qoppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\985")
, (Text
"\\qprime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8279")
, (Text
"\\quarternote",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9833")
, (Text
"\\questeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8799")
, (Text
"\\question",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"?")
, (Text
"\\rAngle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10219")
, (Text
"\\rBrace",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10628")
, (Text
"\\rBrack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10215")
, (Text
"\\rParen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10630")
, (Text
"\\radiation",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9762")
, (Text
"\\rang",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10219")
, (Text
"\\rangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10217")
, (Text
"\\rangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\12297")
, (Text
"\\rangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\9002")
, (Text
"\\rangledot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10642")
, (Text
"\\rangledownzigzagarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9084")
, (Text
"\\rbag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10182")
, (Text
"\\rblkbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10648")
, (Text
"\\rblot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10634")
, (Text
"\\rbrace",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"}")
, (Text
"\\rbracelend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9133")
, (Text
"\\rbracemid",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9132")
, (Text
"\\rbraceuend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9131")
, (Text
"\\rbrack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"]")
, (Text
"\\rbrackextender",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9125")
, (Text
"\\rbracklend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9126")
, (Text
"\\rbracklrtick",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10638")
, (Text
"\\rbrackubar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10636")
, (Text
"\\rbrackuend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9124")
, (Text
"\\rbrackurtick",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10640")
, (Text
"\\rbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10099")
, (Text
"\\rbrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\12309")
, (Text
"\\rceil",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\8969")
, (Text
"\\rcurvyangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10749")
, (Text
"\\rdiagovfdiag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10539")
, (Text
"\\rdiagovsearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10544")
, (Text
"\\recycle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9851")
, (Text
"\\rel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8596")
, (Text
"\\restriction",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8638")
, (Text
"\\revangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10659")
, (Text
"\\revangleubar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10661")
, (Text
"\\revemptyset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10672")
, (Text
"\\revequilibrium",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8651")
, (Text
"\\revnmid",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10990")
, (Text
"\\rfbowtie",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10706")
, (Text
"\\rfloor",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\8971")
, (Text
"\\rftimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10709")
, (Text
"\\rgroup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10223")
, (Text
"\\rightangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8735")
, (Text
"\\rightanglemdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10653")
, (Text
"\\rightanglesqr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10652")
, (Text
"\\rightarrowapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10613")
, (Text
"\\rightarrowbackapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11080")
, (Text
"\\rightarrowbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8677")
, (Text
"\\rightarrowbsimilar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11084")
, (Text
"\\rightarrowdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10526")
, (Text
"\\rightarrowgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11075")
, (Text
"\\rightarrowonoplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10228")
, (Text
"\\rightarrowplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10565")
, (Text
"\\rightarrowshortleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10562")
, (Text
"\\rightarrowsimilar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10612")
, (Text
"\\rightarrowsupset",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11076")
, (Text
"\\rightarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8611")
, (Text
"\\rightarrowtriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8702")
, (Text
"\\rightarrowx",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10567")
, (Text
"\\rightbarharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10604")
, (Text
"\\rightbkarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10509")
, (Text
"\\rightcurvedarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10547")
, (Text
"\\rightdasharrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8674")
, (Text
"\\rightdbltail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10524")
, (Text
"\\rightdotarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10513")
, (Text
"\\rightdowncurvedarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10551")
, (Text
"\\rightfishtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10621")
, (Text
"\\rightharpoonaccent",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8401")
, (Text
"\\rightharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8641")
, (Text
"\\rightharpoondownbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10583")
, (Text
"\\rightharpoonsupdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10596")
, (Text
"\\rightharpoonup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8640")
, (Text
"\\rightharpoonupbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10579")
, (Text
"\\rightharpoonupdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10604")
, (Text
"\\rightimply",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10608")
, (Text
"\\rightleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8644")
, (Text
"\\rightleftarrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8644")
, (Text
"\\rightleftharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10571")
, (Text
"\\rightleftharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8652")
, (Text
"\\rightleftharpoonsdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10601")
, (Text
"\\rightleftharpoonsup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10600")
, (Text
"\\rightmoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9789")
, (Text
"\\rightouterjoin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10198")
, (Text
"\\rightpentagon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11092")
, (Text
"\\rightpentagonblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11091")
, (Text
"\\rightrightarrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8649")
, (Text
"\\rightrightharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10596")
, (Text
"\\rightslice",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10919")
, (Text
"\\rightsquigarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8669")
, (Text
"\\righttail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10522")
, (Text
"\\rightthreearrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8694")
, (Text
"\\rightthreetimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8908")
, (Text
"\\rightturn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8635")
, (Text
"\\rightupdownharpoon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10575")
, (Text
"\\rightwavearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8605")
, (Text
"\\rightwhitearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8680")
, (Text
"\\rimg",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10632")
, (Text
"\\ring",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\778")
, (Text
"\\ringplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10786")
, (Text
"\\risingdotseq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8787")
, (Text
"\\rmoustache",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9137")
, (Text
"\\rparen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
")")
, (Text
"\\rparenextender",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9119")
, (Text
"\\rparengtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10644")
, (Text
"\\rparenlend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9120")
, (Text
"\\rparenuend",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9118")
, (Text
"\\rppolint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10770")
, (Text
"\\rrangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10634")
, (Text
"\\rrbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10215")
, (Text
"\\rrbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\12315")
, (Text
"\\rres",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9655")
, (Text
"\\rrparenthesis",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10632")
, (Text
"\\rsolbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10743")
, (Text
"\\rsqhook",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10958")
, (Text
"\\rsub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10853")
, (Text
"\\rtriltri",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10702")
, (Text
"\\ruledelayed",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10740")
, (Text
"\\rvboxline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9145")
, (Text
"\\rvzigzag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\10713")
, (Text
"\\sadface",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9785")
, (Text
"\\sagittarius",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9808")
, (Text
"\\sampi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\993")
, (Text
"\\sansLmirrored",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8515")
, (Text
"\\sansLturned",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8514")
, (Text
"\\saturn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9796")
, (Text
"\\scorpio",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9807")
, (Text
"\\scpolint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10771")
, (Text
"\\scurel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8881")
, (Text
"\\sdef",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8793")
, (Text
"\\second",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8243")
, (Text
"\\semi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10783")
, (Text
"\\semicolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Pun Text
";")
, (Text
"\\seovnearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10541")
, (Text
"\\sharp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9839")
, (Text
"\\shortdowntack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10975")
, (Text
"\\shortlefttack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10974")
, (Text
"\\shortrightarrowleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10564")
, (Text
"\\shortuptack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10976")
, (Text
"\\shuffle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10722")
, (Text
"\\simgE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10912")
, (Text
"\\simgtr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10910")
, (Text
"\\similarleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11081")
, (Text
"\\similarrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10610")
, (Text
"\\simlE",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10911")
, (Text
"\\simless",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10909")
, (Text
"\\simminussim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10860")
, (Text
"\\simneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8774")
, (Text
"\\simplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10788")
, (Text
"\\simrdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10859")
, (Text
"\\sinewave",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8767")
, (Text
"\\sixteenthnote",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9836")
, (Text
"\\skull",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9760")
, (Text
"\\slash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8725")
, (Text
"\\slash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"/")
, (Text
"\\smallblacktriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9666")
, (Text
"\\smallblacktriangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9656")
, (Text
"\\smallfrown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8994")
, (Text
"\\smallin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8714")
, (Text
"\\smallni",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8717")
, (Text
"\\smallsetminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8726")
, (Text
"\\smallsmile",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8995")
, (Text
"\\smalltriangledown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9663")
, (Text
"\\smalltriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9667")
, (Text
"\\smalltriangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9657")
, (Text
"\\smalltriangleup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9653")
, (Text
"\\smashtimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10803")
, (Text
"\\smblkcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8226")
, (Text
"\\smblkdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11049")
, (Text
"\\smblklozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11050")
, (Text
"\\smblksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9642")
, (Text
"\\smeparsl",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10724")
, (Text
"\\smileface",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9786")
, (Text
"\\smiley",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9786")
, (Text
"\\smt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10922")
, (Text
"\\smte",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10924")
, (Text
"\\smwhitestar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11090")
, (Text
"\\smwhtcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9702")
, (Text
"\\smwhtdiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8900")
, (Text
"\\smwhtlozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11051")
, (Text
"\\smwhtsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9643")
, (Text
"\\spadesuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9824")
, (Text
"\\spddot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\168")
, (Text
"\\sphat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"^")
, (Text
"\\sphericalangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8738")
, (Text
"\\sphericalangleup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10657")
, (Text
"\\spot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10625")
, (Text
"\\sptilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"~")
, (Text
"\\sqint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10774")
, (Text
"\\sqlozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8977")
, (Text
"\\sqrint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10774")
, (Text
"\\sqrt",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rad Text
"\8730")
, (Text
"\\sqrt[3]",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rad Text
"\8731")
, (Text
"\\sqrt[4]",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rad Text
"\8732")
, (Text
"\\sqrtbottom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9143")
, (Text
"\\sqsubsetneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8932")
, (Text
"\\sqsupsetneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8933")
, (Text
"\\squarebotblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11027")
, (Text
"\\squarecrossfill",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9641")
, (Text
"\\squarehfill",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9636")
, (Text
"\\squarehvfill",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9638")
, (Text
"\\squareleftblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9703")
, (Text
"\\squarellblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11029")
, (Text
"\\squarellquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9713")
, (Text
"\\squarelrblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9706")
, (Text
"\\squarelrquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9714")
, (Text
"\\squareneswfill",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9640")
, (Text
"\\squarenwsefill",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9639")
, (Text
"\\squarerightblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9704")
, (Text
"\\squaretopblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11026")
, (Text
"\\squareulblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9705")
, (Text
"\\squareulquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9712")
, (Text
"\\squareurblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11028")
, (Text
"\\squareurquad",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9715")
, (Text
"\\squarevfill",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9637")
, (Text
"\\squoval",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9634")
, (Text
"\\sslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\11005")
, (Text
"\\stareq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8795")
, (Text
"\\steaming",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9749")
, (Text
"\\sterling",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\163")
, (Text
"\\stigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\987")
, (Text
"\\strictfi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10620")
, (Text
"\\strictif",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10621")
, (Text
"\\strns",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9188")
, (Text
"\\subedot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10947")
, (Text
"\\submult",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10945")
, (Text
"\\subrarr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10617")
, (Text
"\\subsetapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10953")
, (Text
"\\subsetcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10179")
, (Text
"\\subsetdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10941")
, (Text
"\\subseteqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10949")
, (Text
"\\subsetneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8842")
, (Text
"\\subsetneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10955")
, (Text
"\\subsetplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10943")
, (Text
"\\subsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10951")
, (Text
"\\subsub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10965")
, (Text
"\\subsup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10963")
, (Text
"\\succapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10936")
, (Text
"\\succcurlyeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8829")
, (Text
"\\succeqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10932")
, (Text
"\\succnapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10938")
, (Text
"\\succneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10930")
, (Text
"\\succneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10934")
, (Text
"\\succnsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8937")
, (Text
"\\succsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8831")
, (Text
"\\sumbottom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9139")
, (Text
"\\sumint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10763")
, (Text
"\\sumtop",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9138")
, (Text
"\\sun",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9788")
, (Text
"\\supdsub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10968")
, (Text
"\\supedot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10948")
, (Text
"\\suphsol",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10185")
, (Text
"\\suphsub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10967")
, (Text
"\\suplarr",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10619")
, (Text
"\\supmult",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10946")
, (Text
"\\supsetapprox",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10954")
, (Text
"\\supsetcirc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10180")
, (Text
"\\supsetdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10942")
, (Text
"\\supseteqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10950")
, (Text
"\\supsetneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8843")
, (Text
"\\supsetneqq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10956")
, (Text
"\\supsetplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10944")
, (Text
"\\supsim",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10952")
, (Text
"\\supsub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10964")
, (Text
"\\supsup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10966")
, (Text
"\\swords",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9876")
, (Text
"\\talloblong",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\11006")
, (Text
"\\taurus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9801")
, (Text
"\\tcmu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\181")
, (Text
"\\tcohm",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8486")
, (Text
"\\thermod",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10727")
, (Text
"\\third",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8244")
, (Text
"\\threedangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10176")
, (Text
"\\threedotcolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10998")
, (Text
"\\threeunderdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8424")
, (Text
"\\tieconcat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8256")
, (Text
"\\tieinfty",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10717")
, (Text
"\\tilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\771")
, (Text
"\\timesbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10801")
, (Text
"\\tinj",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8611")
, (Text
"\\tminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10751")
, (Text
"\\toea",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10536")
, (Text
"\\tona",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10535")
, (Text
"\\topbot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9014")
, (Text
"\\topcir",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10993")
, (Text
"\\topfork",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10970")
, (Text
"\\topsemicircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9696")
, (Text
"\\tosa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10537")
, (Text
"\\towa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10538")
, (Text
"\\tplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10750")
, (Text
"\\trapezium",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9186")
, (Text
"\\trianglecdot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9708")
, (Text
"\\triangledown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9663")
, (Text
"\\triangleleftblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9709")
, (Text
"\\trianglelefteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8884")
, (Text
"\\triangleminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10810")
, (Text
"\\triangleodot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10698")
, (Text
"\\triangleplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10809")
, (Text
"\\triangleq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8796")
, (Text
"\\trianglerightblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9710")
, (Text
"\\trianglerighteq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8885")
, (Text
"\\triangles",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10700")
, (Text
"\\triangleserifs",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10701")
, (Text
"\\triangletimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10811")
, (Text
"\\triangleubar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10699")
, (Text
"\\tripleplus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10747")
, (Text
"\\trprime",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8244")
, (Text
"\\trslash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\11003")
, (Text
"\\tsur",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8608")
, (Text
"\\turnangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10658")
, (Text
"\\turnediota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\8489")
, (Text
"\\turnednot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8985")
, (Text
"\\twocaps",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10827")
, (Text
"\\twocups",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10826")
, (Text
"\\twoheaddownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8609")
, (Text
"\\twoheadleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8606")
, (Text
"\\twoheadleftarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11067")
, (Text
"\\twoheadleftdbkarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11063")
, (Text
"\\twoheadmapsfrom",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\11062")
, (Text
"\\twoheadmapsto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10501")
, (Text
"\\twoheadrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8608")
, (Text
"\\twoheadrightarrowtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10518")
, (Text
"\\twoheaduparrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8607")
, (Text
"\\twoheaduparrowcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10569")
, (Text
"\\twolowline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8215")
, (Text
"\\twonotes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9835")
, (Text
"\\typecolon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10626")
, (Text
"\\ubrbrak",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9185")
, (Text
"\\ularc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9692")
, (Text
"\\ulblacktriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9700")
, (Text
"\\ulcorner",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"\8988")
, (Text
"\\ultriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9720")
, (Text
"\\uminus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10817")
, (Text
"\\underbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TUnder Text
"\817")
, (Text
"\\underbrace",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TUnder Text
"\9183")
, (Text
"\\underbracket",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TUnder Text
"\9141")
, (Text
"\\underleftarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8430")
, (Text
"\\underleftharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8429")
, (Text
"\\underline",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TUnder Text
"_")
, (Text
"\\underparen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TUnder Text
"\9181")
, (Text
"\\underrightarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8431")
, (Text
"\\underrightharpoondown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8428")
, (Text
"\\unicodecdots",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8943")
, (Text
"\\unicodeellipsis",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8230")
, (Text
"\\upAlpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\913")
, (Text
"\\upBeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\914")
, (Text
"\\upChi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\935")
, (Text
"\\upDelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\916")
, (Text
"\\upDigamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\988")
, (Text
"\\upEpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\917")
, (Text
"\\upEta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\919")
, (Text
"\\upGamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\915")
, (Text
"\\upIota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\921")
, (Text
"\\upKappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\922")
, (Text
"\\upKoppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\990")
, (Text
"\\upLambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\923")
, (Text
"\\upMu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\924")
, (Text
"\\upNu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\925")
, (Text
"\\upOmega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\937")
, (Text
"\\upOmicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\927")
, (Text
"\\upPhi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\934")
, (Text
"\\upPi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\928")
, (Text
"\\upPsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\936")
, (Text
"\\upRho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\929")
, (Text
"\\upSampi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\992")
, (Text
"\\upSigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\931")
, (Text
"\\upStigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\986")
, (Text
"\\upTau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\932")
, (Text
"\\upTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\920")
, (Text
"\\upUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\933")
, (Text
"\\upUpsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\978")
, (Text
"\\upXi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\926")
, (Text
"\\upZeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\918")
, (Text
"\\upalpha",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\945")
, (Text
"\\upand",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8523")
, (Text
"\\uparrowbarred",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10505")
, (Text
"\\uparrowdownarrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8645")
, (Text
"\\uparrowoncircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10685")
, (Text
"\\upbackepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\1014")
, (Text
"\\upbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\946")
, (Text
"\\upchi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\967")
, (Text
"\\updasharrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8673")
, (Text
"\\updelta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\948")
, (Text
"\\updigamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\989")
, (Text
"\\updownarrowbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8616")
, (Text
"\\updownarrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8645")
, (Text
"\\updownharpoonleftleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10577")
, (Text
"\\updownharpoonleftright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10573")
, (Text
"\\updownharpoonrightleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10572")
, (Text
"\\updownharpoonrightright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10575")
, (Text
"\\updownharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10606")
, (Text
"\\updownharpoonsleftright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10606")
, (Text
"\\upepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\949")
, (Text
"\\upequilibrium",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10606")
, (Text
"\\upeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\951")
, (Text
"\\upfishtail",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10622")
, (Text
"\\upgamma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\947")
, (Text
"\\upharpoonleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8639")
, (Text
"\\upharpoonleftbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10592")
, (Text
"\\upharpoonleftdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8643")
, (Text
"\\upharpoonleftup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8639")
, (Text
"\\upharpoonright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8638")
, (Text
"\\upharpoonrightbar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10588")
, (Text
"\\upharpoonrightdown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8642")
, (Text
"\\upharpoonsleftright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10595")
, (Text
"\\upin",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10194")
, (Text
"\\upint",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10779")
, (Text
"\\upiota",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\953")
, (Text
"\\upkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\954")
, (Text
"\\upkoppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\991")
, (Text
"\\uplambda",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\955")
, (Text
"\\upmu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\956")
, (Text
"\\upnu",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\957")
, (Text
"\\upoldKoppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\984")
, (Text
"\\upoldkoppa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\985")
, (Text
"\\upomega",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\969")
, (Text
"\\upomicron",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\959")
, (Text
"\\upphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\981")
, (Text
"\\uppi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\960")
, (Text
"\\uppsi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\968")
, (Text
"\\uprevequilibrium",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10607")
, (Text
"\\uprho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\961")
, (Text
"\\uprightcurvearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10548")
, (Text
"\\upsampi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\993")
, (Text
"\\upsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\963")
, (Text
"\\upstigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\987")
, (Text
"\\uptau",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\964")
, (Text
"\\uptheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\952")
, (Text
"\\upuparrows",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8648")
, (Text
"\\upupharpoons",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10595")
, (Text
"\\upupsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\965")
, (Text
"\\upvarTheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\1012")
, (Text
"\\upvarbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\976")
, (Text
"\\upvarepsilon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\1013")
, (Text
"\\upvarkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\1008")
, (Text
"\\upvarphi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\966")
, (Text
"\\upvarpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\982")
, (Text
"\\upvarrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\1009")
, (Text
"\\upvarsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\962")
, (Text
"\\upvartheta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\977")
, (Text
"\\upwhitearrow",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8679")
, (Text
"\\upxi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\958")
, (Text
"\\upzeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\950")
, (Text
"\\uranus",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9797")
, (Text
"\\urarc",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9693")
, (Text
"\\urblacktriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9701")
, (Text
"\\urcorner",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"\8989")
, (Text
"\\urtriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9721")
, (Text
"\\utilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\816")
, (Text
"\\vBar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10984")
, (Text
"\\vBarv",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10985")
, (Text
"\\vDash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8872")
, (Text
"\\vDdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10978")
, (Text
"\\varEarth",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9793")
, (Text
"\\varVdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10982")
, (Text
"\\varbarwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8965")
, (Text
"\\varbeta",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\976")
, (Text
"\\varcarriagereturn",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9166")
, (Text
"\\varclub",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9831")
, (Text
"\\varclubsuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9831")
, (Text
"\\vardiamond",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9830")
, (Text
"\\vardiamondsuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9830")
, (Text
"\\vardoublebarwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8966")
, (Text
"\\varheart",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9829")
, (Text
"\\varheartsuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9829")
, (Text
"\\varhexagon",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11041")
, (Text
"\\varhexagonblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11042")
, (Text
"\\varhexagonlrbonds",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9004")
, (Text
"\\varisinobar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8950")
, (Text
"\\varisins",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8947")
, (Text
"\\varkappa",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120600")
, (Text
"\\varlrtriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8895")
, (Text
"\\varniobar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8957")
, (Text
"\\varnis",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8955")
, (Text
"\\varnothing",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8709")
, (Text
"\\varnothing",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8960")
, (Text
"\\varointclockwise",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\8754")
, (Text
"\\varparallel",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\11005")
, (Text
"\\varpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120603")
, (Text
"\\varpi",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\982")
, (Text
"\\varprod",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10761")
, (Text
"\\varpropto",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8733")
, (Text
"\\varrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\1009")
, (Text
"\\varrho",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120602")
, (Text
"\\varsdef",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8796")
, (Text
"\\varsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\120589")
, (Text
"\\varsigma",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Alpha Text
"\962")
, (Text
"\\varspade",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9828")
, (Text
"\\varspadesuit",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9828")
, (Text
"\\varstar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10038")
, (Text
"\\varsubsetneq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8842")
, (Text
"\\vartriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\9653")
, (Text
"\\vartriangleleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8882")
, (Text
"\\vartriangleright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8883")
, (Text
"\\varveebar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10849")
, (Text
"\\vbraceextender",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9130")
, (Text
"\\vbrtri",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10704")
, (Text
"\\vec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8401")
, (Text
"\\vec",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8407")
, (Text
"\\vectimes",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10799")
, (Text
"\\veebar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8891")
, (Text
"\\veedot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10183")
, (Text
"\\veedoublebar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10851")
, (Text
"\\veeeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8794")
, (Text
"\\veemidvert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10843")
, (Text
"\\veeodot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10834")
, (Text
"\\veeonvee",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10838")
, (Text
"\\veeonwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10841")
, (Text
"\\vert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Fence Text
"|")
, (Text
"\\vertoverlay",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8402")
, (Text
"\\viewdata",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8983")
, (Text
"\\virgo",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9805")
, (Text
"\\vlongdash",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\10205")
, (Text
"\\vrectangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9647")
, (Text
"\\vrectangleblack",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9646")
, (Text
"\\vysmblkcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8729")
, (Text
"\\vysmblksquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11037")
, (Text
"\\vysmwhtcircle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\8728")
, (Text
"\\vysmwhtsquare",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11038")
, (Text
"\\vzigzag",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10650")
, (Text
"\\warning",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9888")
, (Text
"\\wasylozenge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8977")
, (Text
"\\wasytherefore",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8756")
, (Text
"\\wedgebar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10847")
, (Text
"\\wedgedot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10193")
, (Text
"\\wedgedoublebar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10848")
, (Text
"\\wedgemidvert",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10842")
, (Text
"\\wedgeodot",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10833")
, (Text
"\\wedgeonwedge",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10837")
, (Text
"\\wedgeq",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\8793")
, (Text
"\\whitearrowupfrombar",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\8682")
, (Text
"\\whiteinwhitetriangle",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10177")
, (Text
"\\whitepointerleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9669")
, (Text
"\\whitepointerright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9659")
, (Text
"\\whitesquaretickleft",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10212")
, (Text
"\\whitesquaretickright",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Bin Text
"\10213")
, (Text
"\\whthorzoval",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11053")
, (Text
"\\whtvertoval",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\11055")
, (Text
"\\wideangledown",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10662")
, (Text
"\\wideangleup",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\10663")
, (Text
"\\widebridgeabove",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\8425")
, (Text
"\\widehat",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\770")
, (Text
"\\wideparen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
TOver Text
"\9180")
, (Text
"\\widetilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\771")
, (Text
"\\wideutilde",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Accent Text
"\816")
, (Text
"\\xbsol",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10745")
, (Text
"\\xsol",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10744")
, (Text
"\\yen",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\165")
, (Text
"\\yinyang",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Ord Text
"\9775")
, (Text
"\\zcmp",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10783")
, (Text
"\\zhide",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10745")
, (Text
"\\zpipe",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10784")
, (Text
"\\zproject",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Op Text
"\10785")
, (Text
"\\{",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Open Text
"{")
, (Text
"\\|",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Fence Text
"\8214")
, (Text
"\\}",TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Close Text
"}")
]
textual :: TP Text
textual :: TP Text
textual = TP Text
regular TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text
sps TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text
ligature TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text
textCommand
TP Text -> SourceName -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> SourceName -> ParsecT s u m a
<?> SourceName
"text"
sps :: TP Text
sps :: TP Text
sps = Text
" " Text -> ParsecT Text () Identity () -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 (SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
oneOf SourceName
" \t\n")
regular :: TP Text
regular :: TP Text
regular = SourceName -> Text
T.pack (SourceName -> Text)
-> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
-> ParsecT Text () Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (SourceName -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m Char
noneOf SourceName
"`'-~${}\\ \t")
ligature :: TP Text
ligature :: TP Text
ligature = TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
"\x2014" Text -> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"---")
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
"\x2013" Text -> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"--")
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text -> TP Text
textStr Text
"-")
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
"\x201C" Text -> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"``")
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
"\x201D" Text -> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"''")
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
"\x2019" Text -> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"'")
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
"\x2018" Text -> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"`")
TP Text -> TP Text -> TP Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
"\xA0" Text -> ParsecT Text () Identity SourceName -> TP Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"~")
textCommand :: TP Text
textCommand :: TP Text
textCommand = do
Text
cmd <- [Text] -> TP Text
oneOfCommands (Map Text (TP Text) -> [Text]
forall k a. Map k a -> [k]
M.keys Map Text (TP Text)
textCommands)
ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Text () Identity Char -> ParsecT Text () Identity ())
-> ParsecT Text () Identity Char -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity ()
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}')
case Text -> Map Text (TP Text) -> Maybe (TP Text)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
cmd Map Text (TP Text)
textCommands of
Maybe (TP Text)
Nothing -> SourceName -> TP Text
forall (m :: * -> *) a. MonadFail m => SourceName -> m a
fail (SourceName -> TP Text) -> SourceName -> TP Text
forall a b. (a -> b) -> a -> b
$ Text -> SourceName
T.unpack (Text -> SourceName) -> Text -> SourceName
forall a b. (a -> b) -> a -> b
$ Text
"Unknown control sequence " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cmd
Just TP Text
c -> TP Text
c
tok :: TP Char
tok :: ParsecT Text () Identity Char
tok = (ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text () Identity Char -> ParsecT Text () Identity Char)
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity ()
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity Char
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}')
ParsecT Text () Identity Char
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar
textCommands :: M.Map Text (TP Text)
textCommands :: Map Text (TP Text)
textCommands = [(Text, TP Text)] -> Map Text (TP Text)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"\\#", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"#")
, (Text
"\\$", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"$")
, (Text
"\\%", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"%")
, (Text
"\\&", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"&")
, (Text
"\\_", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"_")
, (Text
"\\{", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"{")
, (Text
"\\}", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"}")
, (Text
"\\ldots", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\x2026")
, (Text
"\\textasciitilde", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"~")
, (Text
"\\textasciicircum", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"^")
, (Text
"\\textbackslash", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\\")
, (Text
"\\char", TP Text
parseC)
, (Text
"\\aa", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"å")
, (Text
"\\AA", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"Å")
, (Text
"\\ss", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"ß")
, (Text
"\\o", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"ø")
, (Text
"\\O", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"Ø")
, (Text
"\\L", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"Ł")
, (Text
"\\l", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"ł")
, (Text
"\\ae", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"æ")
, (Text
"\\AE", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"Æ")
, (Text
"\\oe", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"œ")
, (Text
"\\OE", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"Œ")
, (Text
"\\`", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"`" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
grave (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\'", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"'" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
acute (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\^", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"^" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
circ (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\~", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"~" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
tilde (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\\"", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"\"" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
umlaut (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\.", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"." (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
dot (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\=", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"=" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
macron (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\c", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"c" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
cedilla (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\v", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"v" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
hacek (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\u", Text -> TP Text -> TP Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"u" (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
breve (Char -> Text) -> ParsecT Text () Identity Char -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text () Identity Char
tok)
, (Text
"\\ ", Text -> TP Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
" ")
]
parseC :: TP Text
parseC :: TP Text
parseC = TP Text -> TP Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Text -> TP Text) -> TP Text -> TP Text
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'`' ParsecT Text () Identity Char -> TP Text -> TP Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Line -> ParsecT Text () Identity Char -> TP Text
countChar Line
1 ParsecT Text () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar
grave :: Char -> Text
grave :: Char -> Text
grave Char
'A' = Text
"À"
grave Char
'E' = Text
"È"
grave Char
'I' = Text
"Ì"
grave Char
'O' = Text
"Ò"
grave Char
'U' = Text
"Ù"
grave Char
'a' = Text
"à"
grave Char
'e' = Text
"è"
grave Char
'i' = Text
"ì"
grave Char
'o' = Text
"ò"
grave Char
'u' = Text
"ù"
grave Char
c = Char -> Text
T.singleton Char
c
acute :: Char -> Text
acute :: Char -> Text
acute Char
'A' = Text
"Á"
acute Char
'E' = Text
"É"
acute Char
'I' = Text
"Í"
acute Char
'O' = Text
"Ó"
acute Char
'U' = Text
"Ú"
acute Char
'Y' = Text
"Ý"
acute Char
'a' = Text
"á"
acute Char
'e' = Text
"é"
acute Char
'i' = Text
"í"
acute Char
'o' = Text
"ó"
acute Char
'u' = Text
"ú"
acute Char
'y' = Text
"ý"
acute Char
'C' = Text
"Ć"
acute Char
'c' = Text
"ć"
acute Char
'L' = Text
"Ĺ"
acute Char
'l' = Text
"ĺ"
acute Char
'N' = Text
"Ń"
acute Char
'n' = Text
"ń"
acute Char
'R' = Text
"Ŕ"
acute Char
'r' = Text
"ŕ"
acute Char
'S' = Text
"Ś"
acute Char
's' = Text
"ś"
acute Char
'Z' = Text
"Ź"
acute Char
'z' = Text
"ź"
acute Char
c = Char -> Text
T.singleton Char
c
circ :: Char -> Text
circ :: Char -> Text
circ Char
'A' = Text
"Â"
circ Char
'E' = Text
"Ê"
circ Char
'I' = Text
"Î"
circ Char
'O' = Text
"Ô"
circ Char
'U' = Text
"Û"
circ Char
'a' = Text
"â"
circ Char
'e' = Text
"ê"
circ Char
'i' = Text
"î"
circ Char
'o' = Text
"ô"
circ Char
'u' = Text
"û"
circ Char
'C' = Text
"Ĉ"
circ Char
'c' = Text
"ĉ"
circ Char
'G' = Text
"Ĝ"
circ Char
'g' = Text
"ĝ"
circ Char
'H' = Text
"Ĥ"
circ Char
'h' = Text
"ĥ"
circ Char
'J' = Text
"Ĵ"
circ Char
'j' = Text
"ĵ"
circ Char
'S' = Text
"Ŝ"
circ Char
's' = Text
"ŝ"
circ Char
'W' = Text
"Ŵ"
circ Char
'w' = Text
"ŵ"
circ Char
'Y' = Text
"Ŷ"
circ Char
'y' = Text
"ŷ"
circ Char
c = Char -> Text
T.singleton Char
c
tilde :: Char -> Text
tilde :: Char -> Text
tilde Char
'A' = Text
"Ã"
tilde Char
'a' = Text
"ã"
tilde Char
'O' = Text
"Õ"
tilde Char
'o' = Text
"õ"
tilde Char
'I' = Text
"Ĩ"
tilde Char
'i' = Text
"ĩ"
tilde Char
'U' = Text
"Ũ"
tilde Char
'u' = Text
"ũ"
tilde Char
'N' = Text
"Ñ"
tilde Char
'n' = Text
"ñ"
tilde Char
c = Char -> Text
T.singleton Char
c
umlaut :: Char -> Text
umlaut :: Char -> Text
umlaut Char
'A' = Text
"Ä"
umlaut Char
'E' = Text
"Ë"
umlaut Char
'I' = Text
"Ï"
umlaut Char
'O' = Text
"Ö"
umlaut Char
'U' = Text
"Ü"
umlaut Char
'a' = Text
"ä"
umlaut Char
'e' = Text
"ë"
umlaut Char
'i' = Text
"ï"
umlaut Char
'o' = Text
"ö"
umlaut Char
'u' = Text
"ü"
umlaut Char
c = Char -> Text
T.singleton Char
c
dot :: Char -> Text
dot :: Char -> Text
dot Char
'C' = Text
"Ċ"
dot Char
'c' = Text
"ċ"
dot Char
'E' = Text
"Ė"
dot Char
'e' = Text
"ė"
dot Char
'G' = Text
"Ġ"
dot Char
'g' = Text
"ġ"
dot Char
'I' = Text
"İ"
dot Char
'Z' = Text
"Ż"
dot Char
'z' = Text
"ż"
dot Char
c = Char -> Text
T.singleton Char
c
macron :: Char -> Text
macron :: Char -> Text
macron Char
'A' = Text
"Ā"
macron Char
'E' = Text
"Ē"
macron Char
'I' = Text
"Ī"
macron Char
'O' = Text
"Ō"
macron Char
'U' = Text
"Ū"
macron Char
'a' = Text
"ā"
macron Char
'e' = Text
"ē"
macron Char
'i' = Text
"ī"
macron Char
'o' = Text
"ō"
macron Char
'u' = Text
"ū"
macron Char
c = Char -> Text
T.singleton Char
c
cedilla :: Char -> Text
cedilla :: Char -> Text
cedilla Char
'c' = Text
"ç"
cedilla Char
'C' = Text
"Ç"
cedilla Char
's' = Text
"ş"
cedilla Char
'S' = Text
"Ş"
cedilla Char
't' = Text
"ţ"
cedilla Char
'T' = Text
"Ţ"
cedilla Char
'e' = Text
"ȩ"
cedilla Char
'E' = Text
"Ȩ"
cedilla Char
'h' = Text
"ḩ"
cedilla Char
'H' = Text
"Ḩ"
cedilla Char
'o' = Text
"o̧"
cedilla Char
'O' = Text
"O̧"
cedilla Char
c = Char -> Text
T.singleton Char
c
hacek :: Char -> Text
hacek :: Char -> Text
hacek Char
'A' = Text
"Ǎ"
hacek Char
'a' = Text
"ǎ"
hacek Char
'C' = Text
"Č"
hacek Char
'c' = Text
"č"
hacek Char
'D' = Text
"Ď"
hacek Char
'd' = Text
"ď"
hacek Char
'E' = Text
"Ě"
hacek Char
'e' = Text
"ě"
hacek Char
'G' = Text
"Ǧ"
hacek Char
'g' = Text
"ǧ"
hacek Char
'H' = Text
"Ȟ"
hacek Char
'h' = Text
"ȟ"
hacek Char
'I' = Text
"Ǐ"
hacek Char
'i' = Text
"ǐ"
hacek Char
'j' = Text
"ǰ"
hacek Char
'K' = Text
"Ǩ"
hacek Char
'k' = Text
"ǩ"
hacek Char
'L' = Text
"Ľ"
hacek Char
'l' = Text
"ľ"
hacek Char
'N' = Text
"Ň"
hacek Char
'n' = Text
"ň"
hacek Char
'O' = Text
"Ǒ"
hacek Char
'o' = Text
"ǒ"
hacek Char
'R' = Text
"Ř"
hacek Char
'r' = Text
"ř"
hacek Char
'S' = Text
"Š"
hacek Char
's' = Text
"š"
hacek Char
'T' = Text
"Ť"
hacek Char
't' = Text
"ť"
hacek Char
'U' = Text
"Ǔ"
hacek Char
'u' = Text
"ǔ"
hacek Char
'Z' = Text
"Ž"
hacek Char
'z' = Text
"ž"
hacek Char
c = Char -> Text
T.singleton Char
c
breve :: Char -> Text
breve :: Char -> Text
breve Char
'A' = Text
"Ă"
breve Char
'a' = Text
"ă"
breve Char
'E' = Text
"Ĕ"
breve Char
'e' = Text
"ĕ"
breve Char
'G' = Text
"Ğ"
breve Char
'g' = Text
"ğ"
breve Char
'I' = Text
"Ĭ"
breve Char
'i' = Text
"ĭ"
breve Char
'O' = Text
"Ŏ"
breve Char
'o' = Text
"ŏ"
breve Char
'U' = Text
"Ŭ"
breve Char
'u' = Text
"ŭ"
breve Char
c = Char -> Text
T.singleton Char
c
siunitx :: Text -> TP Exp
siunitx :: Text -> TP Exp
siunitx Text
c = do
case Text
c of
Text
"\\si" -> TP Exp
dosi
Text
"\\SI" -> TP Exp
doSI
Text
"\\SIrange" -> Bool -> TP Exp
doSIrange Bool
True
Text
"\\numrange" -> Bool -> TP Exp
doSIrange Bool
False
Text
"\\numlist" -> TP Exp
doSInumlist
Text
"\\num" -> TP Exp
doSInum
Text
"\\ang" -> TP Exp
doSIang
Text
_ -> TP Exp
forall (m :: * -> *) a. MonadPlus m => m a
mzero
doSIrange :: Bool -> TP Exp
doSIrange :: Bool -> TP Exp
doSIrange Bool
includeUnits = do
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Text () Identity () -> ParsecT Text () Identity ())
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ TP Exp -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TP Exp
inbrackets
Maybe Exp
startvalue <- Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Exp -> Maybe Exp)
-> TP Exp -> ParsecT Text () Identity (Maybe Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
doSInum
Maybe Exp
startvalueprefix <- Maybe Exp
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Maybe Exp
forall a. Maybe a
Nothing (ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp))
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall a b. (a -> b) -> a -> b
$ Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Exp -> Maybe Exp)
-> TP Exp -> ParsecT Text () Identity (Maybe Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp -> TP Exp
forall a. TP a -> TP a
brackets TP Exp
expr
Maybe Exp
stopvalue <- Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Exp -> Maybe Exp)
-> TP Exp -> ParsecT Text () Identity (Maybe Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
doSInum
Maybe Exp
stopvalueprefix <- Maybe Exp
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Maybe Exp
forall a. Maybe a
Nothing (ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp))
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall a b. (a -> b) -> a -> b
$ Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Exp -> Maybe Exp)
-> TP Exp -> ParsecT Text () Identity (Maybe Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp -> TP Exp
forall a. TP a -> TP a
brackets TP Exp
expr
Maybe Exp
unit <- if Bool
includeUnits
then Maybe Exp
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Maybe Exp
forall a. Maybe a
Nothing (ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp))
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall a b. (a -> b) -> a -> b
$ Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Exp -> Maybe Exp)
-> TP Exp -> ParsecT Text () Identity (Maybe Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
dosi
else Maybe Exp -> ParsecT Text () Identity (Maybe Exp)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Exp
forall a. Maybe a
Nothing
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped ([Exp] -> Exp) -> [Exp] -> Exp
forall a b. (a -> b) -> a -> b
$ [Maybe Exp] -> [Exp]
forall a. [Maybe a] -> [a]
catMaybes
[Maybe Exp
startvalueprefix,
Maybe Exp -> Maybe Exp
emptyOr160 Maybe Exp
startvalueprefix,
Maybe Exp
startvalue,
Maybe Exp -> Maybe Exp
emptyOr160 Maybe Exp
unit,
Maybe Exp
unit,
Exp -> Maybe Exp
forall a. a -> Maybe a
Just (TextType -> Text -> Exp
EText TextType
TextNormal Text
"\8211"),
Maybe Exp
stopvalueprefix,
Maybe Exp -> Maybe Exp
emptyOr160 Maybe Exp
stopvalueprefix,
Maybe Exp
stopvalue,
Maybe Exp -> Maybe Exp
emptyOr160 Maybe Exp
unit,
Maybe Exp
unit]
doSInumlist :: TP Exp
doSInumlist :: TP Exp
doSInumlist = do
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Text () Identity () -> ParsecT Text () Identity ())
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ TP Exp -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TP Exp
inbrackets
[Exp]
xs <- Parsec Text () [Exp] -> Parsec Text () [Exp]
forall a. TP a -> TP a
braces (TP Exp -> ParsecT Text () Identity Char -> Parsec Text () [Exp]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy TP Exp
siNum (ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity ()
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
';' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces))
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$
case [Exp]
xs of
[] -> [Exp] -> Exp
EGrouped []
[Exp
x] -> Exp
x
[Exp]
_ -> [Exp] -> Exp
EGrouped ([Exp] -> Exp) -> [Exp] -> Exp
forall a b. (a -> b) -> a -> b
$
Exp -> [Exp] -> [Exp]
forall a. a -> [a] -> [a]
intersperse (TextType -> Text -> Exp
EText TextType
TextNormal Text
", ") ([Exp] -> [Exp]
forall a. [a] -> [a]
init [Exp]
xs) [Exp] -> [Exp] -> [Exp]
forall a. [a] -> [a] -> [a]
++
[TextType -> Text -> Exp
EText TextType
TextNormal Text
", & ", [Exp] -> Exp
forall a. [a] -> a
last [Exp]
xs]
dosi :: TP Exp
dosi :: TP Exp
dosi = TP Exp
siUnit TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp -> TP Exp
forall a. TP a -> TP a
braces (TP Exp -> TP Exp
manyExp (TP Exp
siUnit TP Exp -> TP Exp -> TP Exp
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TP Exp
expr))
doSIang :: TP Exp
doSIang :: TP Exp
doSIang = do
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Text () Identity () -> ParsecT Text () Identity ())
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ TP Exp -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TP Exp
inbrackets
[Exp]
ps <- Parsec Text () [Exp] -> Parsec Text () [Exp]
forall a. TP a -> TP a
braces (Parsec Text () [Exp] -> Parsec Text () [Exp])
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall a b. (a -> b) -> a -> b
$ TP Exp -> ParsecT Text () Identity Char -> Parsec Text () [Exp]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy TP Exp
siNum (ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces ParsecT Text () Identity ()
-> ParsecT Text () Identity Char -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Text () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
';' ParsecT Text () Identity Char
-> ParsecT Text () Identity () -> ParsecT Text () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces)
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped ([Exp] -> Exp) -> [Exp] -> Exp
forall a b. (a -> b) -> a -> b
$
case [Exp]
ps [Exp] -> [Exp] -> [Exp]
forall a. [a] -> [a] -> [a]
++ Exp -> [Exp]
forall a. a -> [a]
repeat ([Exp] -> Exp
EGrouped []) of
(Exp
d:Exp
m:Exp
s:[Exp]
_) ->
(if Exp
d Exp -> Exp -> Bool
forall a. Eq a => a -> a -> Bool
== [Exp] -> Exp
EGrouped [] then [] else [Exp
d, TextType -> Text -> Exp
EText TextType
TextNormal Text
"\xb0"]) [Exp] -> [Exp] -> [Exp]
forall a. Semigroup a => a -> a -> a
<>
(if Exp
m Exp -> Exp -> Bool
forall a. Eq a => a -> a -> Bool
== [Exp] -> Exp
EGrouped [] then [] else [Exp
m, TextType -> Text -> Exp
EText TextType
TextNormal Text
"\x2032"]) [Exp] -> [Exp] -> [Exp]
forall a. Semigroup a => a -> a -> a
<>
(if Exp
s Exp -> Exp -> Bool
forall a. Eq a => a -> a -> Bool
== [Exp] -> Exp
EGrouped [] then [] else [Exp
s, TextType -> Text -> Exp
EText TextType
TextNormal Text
"\x2033"])
[Exp]
_ -> []
doSI :: TP Exp
doSI :: TP Exp
doSI = do
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Text () Identity () -> ParsecT Text () Identity ())
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ TP Exp -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TP Exp
inbrackets
Maybe Exp
value <- Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Exp -> Maybe Exp)
-> TP Exp -> ParsecT Text () Identity (Maybe Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
doSInum
Maybe Exp
valueprefix <- Maybe Exp
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Maybe Exp
forall a. Maybe a
Nothing (ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp))
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall a b. (a -> b) -> a -> b
$ do
Exp
x <- TP Exp
inbrackets
if Exp
x Exp -> Exp -> Bool
forall a. Eq a => a -> a -> Bool
== [Exp] -> Exp
EGrouped []
then Maybe Exp -> ParsecT Text () Identity (Maybe Exp)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Exp
forall a. Maybe a
Nothing
else Maybe Exp -> ParsecT Text () Identity (Maybe Exp)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Exp -> ParsecT Text () Identity (Maybe Exp))
-> Maybe Exp -> ParsecT Text () Identity (Maybe Exp)
forall a b. (a -> b) -> a -> b
$ Exp -> Maybe Exp
forall a. a -> Maybe a
Just Exp
x
Maybe Exp
unit <- Maybe Exp
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Maybe Exp
forall a. Maybe a
Nothing (ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp))
-> ParsecT Text () Identity (Maybe Exp)
-> ParsecT Text () Identity (Maybe Exp)
forall a b. (a -> b) -> a -> b
$ Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Exp -> Maybe Exp)
-> TP Exp -> ParsecT Text () Identity (Maybe Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Exp
dosi
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ [Exp] -> Exp
EGrouped ([Exp] -> Exp) -> [Exp] -> Exp
forall a b. (a -> b) -> a -> b
$ [Maybe Exp] -> [Exp]
forall a. [Maybe a] -> [a]
catMaybes
[ Maybe Exp
valueprefix,
Maybe Exp -> Maybe Exp
emptyOr160 Maybe Exp
valueprefix,
Maybe Exp
value,
Maybe Exp -> Maybe Exp
emptyOr160 Maybe Exp
unit,
Maybe Exp
unit
]
emptyOr160 :: Maybe Exp -> Maybe Exp
emptyOr160 :: Maybe Exp -> Maybe Exp
emptyOr160 (Just Exp
_) = Exp -> Maybe Exp
forall a. a -> Maybe a
Just (Rational -> Exp
ESpace (Rational
4Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
18))
emptyOr160 Maybe Exp
Nothing = Maybe Exp
forall a. Maybe a
Nothing
siUnit :: TP Exp
siUnit :: TP Exp
siUnit = TP Exp -> TP Exp
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ do
Text
name <- (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'\\') (Text -> Text) -> TP Text -> TP Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP Text
anyCtrlSeq
case Text
name of
Text
"square" -> do
Exp
unit <- TP Exp
siUnit
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Exp -> Exp -> Exp
ESuper Exp
unit (Text -> Exp
ENumber Text
"2")
Text
"cubic" -> do
Exp
unit <- TP Exp
siUnit
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Exp -> Exp -> Exp
ESuper Exp
unit (Text -> Exp
ENumber Text
"3")
Text
"raisetothe" -> do
Exp
n <- TP Exp
expr
Exp
unit <- TP Exp
siUnit
Exp -> TP Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> TP Exp) -> Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$ Exp -> Exp -> Exp
ESuper Exp
unit Exp
n
Text
_ ->
case Text -> Map Text Exp -> Maybe Exp
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
name Map Text Exp
siUnitMap of
Just Exp
il ->
Exp -> TP Exp -> TP Exp
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Exp
il (TP Exp -> TP Exp) -> TP Exp -> TP Exp
forall a b. (a -> b) -> a -> b
$
[TP Exp] -> TP Exp
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ (Exp -> Exp -> Exp
ESuper Exp
il (Text -> Exp
ENumber Text
"2")) Exp -> ParsecT Text () Identity SourceName -> TP Exp
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"squared"
, (Exp -> Exp -> Exp
ESuper Exp
il (Text -> Exp
ENumber Text
"3")) Exp -> ParsecT Text () Identity SourceName -> TP Exp
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"cubed"
, (\Exp
n -> Exp -> Exp -> Exp
ESuper Exp
il Exp
n) (Exp -> Exp) -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SourceName -> ParsecT Text () Identity SourceName
ctrlseq SourceName
"tothe" ParsecT Text () Identity SourceName -> TP Exp -> TP Exp
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TP Exp
expr)
]
Maybe Exp
Nothing -> SourceName -> TP Exp
forall (m :: * -> *) a. MonadFail m => SourceName -> m a
fail SourceName
"not an siunit unit command"
siUnitMap :: M.Map Text Exp
siUnitMap :: Map Text Exp
siUnitMap = [(Text, Exp)] -> Map Text Exp
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"fg", Text -> Exp
str Text
"fg")
, (Text
"pg", Text -> Exp
str Text
"pg")
, (Text
"ng", Text -> Exp
str Text
"ng")
, (Text
"ug", Text -> Exp
str Text
"μg")
, (Text
"mg", Text -> Exp
str Text
"mg")
, (Text
"g", Text -> Exp
str Text
"g")
, (Text
"kg", Text -> Exp
str Text
"kg")
, (Text
"amu", Text -> Exp
str Text
"u")
, (Text
"pm", Text -> Exp
str Text
"pm")
, (Text
"nm", Text -> Exp
str Text
"nm")
, (Text
"um", Text -> Exp
str Text
"μm")
, (Text
"mm", Text -> Exp
str Text
"mm")
, (Text
"cm", Text -> Exp
str Text
"cm")
, (Text
"dm", Text -> Exp
str Text
"dm")
, (Text
"m", Text -> Exp
str Text
"m")
, (Text
"km", Text -> Exp
str Text
"km")
, (Text
"as", Text -> Exp
str Text
"as")
, (Text
"fs", Text -> Exp
str Text
"fs")
, (Text
"ps", Text -> Exp
str Text
"ps")
, (Text
"ns", Text -> Exp
str Text
"ns")
, (Text
"us", Text -> Exp
str Text
"μs")
, (Text
"ms", Text -> Exp
str Text
"ms")
, (Text
"s", Text -> Exp
str Text
"s")
, (Text
"fmol", Text -> Exp
str Text
"fmol")
, (Text
"pmol", Text -> Exp
str Text
"pmol")
, (Text
"nmol", Text -> Exp
str Text
"nmol")
, (Text
"umol", Text -> Exp
str Text
"μmol")
, (Text
"mmol", Text -> Exp
str Text
"mmol")
, (Text
"mol", Text -> Exp
str Text
"mol")
, (Text
"kmol", Text -> Exp
str Text
"kmol")
, (Text
"pA", Text -> Exp
str Text
"pA")
, (Text
"nA", Text -> Exp
str Text
"nA")
, (Text
"uA", Text -> Exp
str Text
"μA")
, (Text
"mA", Text -> Exp
str Text
"mA")
, (Text
"A", Text -> Exp
str Text
"A")
, (Text
"kA", Text -> Exp
str Text
"kA")
, (Text
"ul", Text -> Exp
str Text
"μl")
, (Text
"ml", Text -> Exp
str Text
"ml")
, (Text
"l", Text -> Exp
str Text
"l")
, (Text
"hl", Text -> Exp
str Text
"hl")
, (Text
"uL", Text -> Exp
str Text
"μL")
, (Text
"mL", Text -> Exp
str Text
"mL")
, (Text
"L", Text -> Exp
str Text
"L")
, (Text
"hL", Text -> Exp
str Text
"hL")
, (Text
"mHz", Text -> Exp
str Text
"mHz")
, (Text
"Hz", Text -> Exp
str Text
"Hz")
, (Text
"kHz", Text -> Exp
str Text
"kHz")
, (Text
"MHz", Text -> Exp
str Text
"MHz")
, (Text
"GHz", Text -> Exp
str Text
"GHz")
, (Text
"THz", Text -> Exp
str Text
"THz")
, (Text
"mN", Text -> Exp
str Text
"mN")
, (Text
"N", Text -> Exp
str Text
"N")
, (Text
"kN", Text -> Exp
str Text
"kN")
, (Text
"MN", Text -> Exp
str Text
"MN")
, (Text
"Pa", Text -> Exp
str Text
"Pa")
, (Text
"kPa", Text -> Exp
str Text
"kPa")
, (Text
"MPa", Text -> Exp
str Text
"MPa")
, (Text
"GPa", Text -> Exp
str Text
"GPa")
, (Text
"mohm", Text -> Exp
str Text
"mΩ")
, (Text
"kohm", Text -> Exp
str Text
"kΩ")
, (Text
"Mohm", Text -> Exp
str Text
"MΩ")
, (Text
"pV", Text -> Exp
str Text
"pV")
, (Text
"nV", Text -> Exp
str Text
"nV")
, (Text
"uV", Text -> Exp
str Text
"μV")
, (Text
"mV", Text -> Exp
str Text
"mV")
, (Text
"V", Text -> Exp
str Text
"V")
, (Text
"kV", Text -> Exp
str Text
"kV")
, (Text
"W", Text -> Exp
str Text
"W")
, (Text
"uW", Text -> Exp
str Text
"μW")
, (Text
"mW", Text -> Exp
str Text
"mW")
, (Text
"kW", Text -> Exp
str Text
"kW")
, (Text
"MW", Text -> Exp
str Text
"MW")
, (Text
"GW", Text -> Exp
str Text
"GW")
, (Text
"J", Text -> Exp
str Text
"J")
, (Text
"uJ", Text -> Exp
str Text
"μJ")
, (Text
"mJ", Text -> Exp
str Text
"mJ")
, (Text
"kJ", Text -> Exp
str Text
"kJ")
, (Text
"eV", Text -> Exp
str Text
"eV")
, (Text
"meV", Text -> Exp
str Text
"meV")
, (Text
"keV", Text -> Exp
str Text
"keV")
, (Text
"MeV", Text -> Exp
str Text
"MeV")
, (Text
"GeV", Text -> Exp
str Text
"GeV")
, (Text
"TeV", Text -> Exp
str Text
"TeV")
, (Text
"kWh", Text -> Exp
str Text
"kWh")
, (Text
"F", Text -> Exp
str Text
"F")
, (Text
"fF", Text -> Exp
str Text
"fF")
, (Text
"pF", Text -> Exp
str Text
"pF")
, (Text
"K", Text -> Exp
str Text
"K")
, (Text
"dB", Text -> Exp
str Text
"dB")
, (Text
"ampere", Text -> Exp
str Text
"A")
, (Text
"angstrom", Text -> Exp
str Text
"Å")
, (Text
"arcmin", Text -> Exp
str Text
"′")
, (Text
"arcminute", Text -> Exp
str Text
"′")
, (Text
"arcsecond", Text -> Exp
str Text
"″")
, (Text
"astronomicalunit", Text -> Exp
str Text
"ua")
, (Text
"atomicmassunit", Text -> Exp
str Text
"u")
, (Text
"atto", Text -> Exp
str Text
"a")
, (Text
"bar", Text -> Exp
str Text
"bar")
, (Text
"barn", Text -> Exp
str Text
"b")
, (Text
"becquerel", Text -> Exp
str Text
"Bq")
, (Text
"bel", Text -> Exp
str Text
"B")
, (Text
"bohr", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"a") (Text -> Exp
ENumber Text
"0"))
, (Text
"candela", Text -> Exp
str Text
"cd")
, (Text
"celsius", Text -> Exp
str Text
"°C")
, (Text
"centi", Text -> Exp
str Text
"c")
, (Text
"clight", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"c") (Text -> Exp
ENumber Text
"0"))
, (Text
"coulomb", Text -> Exp
str Text
"C")
, (Text
"dalton", Text -> Exp
str Text
"Da")
, (Text
"day", Text -> Exp
str Text
"d")
, (Text
"deca", Text -> Exp
str Text
"d")
, (Text
"deci", Text -> Exp
str Text
"d")
, (Text
"decibel", Text -> Exp
str Text
"db")
, (Text
"degreeCelsius",Text -> Exp
str Text
"°C")
, (Text
"degree", Text -> Exp
str Text
"°")
, (Text
"deka", Text -> Exp
str Text
"d")
, (Text
"electronmass", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"m") (TextType -> Text -> Exp
EText TextType
TextItalic Text
"e"))
, (Text
"electronvolt", Text -> Exp
str Text
"eV")
, (Text
"elementarycharge", TextType -> Text -> Exp
EText TextType
TextItalic Text
"e")
, (Text
"exa", Text -> Exp
str Text
"E")
, (Text
"farad", Text -> Exp
str Text
"F")
, (Text
"femto", Text -> Exp
str Text
"f")
, (Text
"giga", Text -> Exp
str Text
"G")
, (Text
"gram", Text -> Exp
str Text
"g")
, (Text
"gray", Text -> Exp
str Text
"Gy")
, (Text
"hartree", Exp -> Exp -> Exp
ESuper (TextType -> Text -> Exp
EText TextType
TextItalic Text
"E") (TextType -> Text -> Exp
EText TextType
TextItalic Text
"h"))
, (Text
"hectare", Text -> Exp
str Text
"ha")
, (Text
"hecto", Text -> Exp
str Text
"h")
, (Text
"henry", Text -> Exp
str Text
"H")
, (Text
"hertz", Text -> Exp
str Text
"Hz")
, (Text
"hour", Text -> Exp
str Text
"h")
, (Text
"joule", Text -> Exp
str Text
"J")
, (Text
"katal", Text -> Exp
str Text
"kat")
, (Text
"kelvin", Text -> Exp
str Text
"K")
, (Text
"kilo", Text -> Exp
str Text
"k")
, (Text
"kilogram", Text -> Exp
str Text
"kg")
, (Text
"knot", Text -> Exp
str Text
"kn")
, (Text
"liter", Text -> Exp
str Text
"L")
, (Text
"litre", Text -> Exp
str Text
"l")
, (Text
"lumen", Text -> Exp
str Text
"lm")
, (Text
"lux", Text -> Exp
str Text
"lx")
, (Text
"mega", Text -> Exp
str Text
"M")
, (Text
"meter", Text -> Exp
str Text
"m")
, (Text
"metre", Text -> Exp
str Text
"m")
, (Text
"micro", Text -> Exp
str Text
"μ")
, (Text
"milli", Text -> Exp
str Text
"m")
, (Text
"minute", Text -> Exp
str Text
"min")
, (Text
"mmHg", Text -> Exp
str Text
"mmHg")
, (Text
"mole", Text -> Exp
str Text
"mol")
, (Text
"nano", Text -> Exp
str Text
"n")
, (Text
"nauticalmile", Text -> Exp
str Text
"M")
, (Text
"neper", Text -> Exp
str Text
"Np")
, (Text
"newton", Text -> Exp
str Text
"N")
, (Text
"ohm", Text -> Exp
str Text
"Ω")
, (Text
"Pa", Text -> Exp
str Text
"Pa")
, (Text
"pascal", Text -> Exp
str Text
"Pa")
, (Text
"percent", Text -> Exp
str Text
"%")
, (Text
"per", Text -> Exp
str Text
"/")
, (Text
"peta", Text -> Exp
str Text
"P")
, (Text
"pico", Text -> Exp
str Text
"p")
, (Text
"planckbar", TextType -> Text -> Exp
EText TextType
TextItalic Text
"\x210f")
, (Text
"radian", Text -> Exp
str Text
"rad")
, (Text
"second", Text -> Exp
str Text
"s")
, (Text
"siemens", Text -> Exp
str Text
"S")
, (Text
"sievert", Text -> Exp
str Text
"Sv")
, (Text
"steradian", Text -> Exp
str Text
"sr")
, (Text
"tera", Text -> Exp
str Text
"T")
, (Text
"tesla", Text -> Exp
str Text
"T")
, (Text
"tonne", Text -> Exp
str Text
"t")
, (Text
"volt", Text -> Exp
str Text
"V")
, (Text
"watt", Text -> Exp
str Text
"W")
, (Text
"weber", Text -> Exp
str Text
"Wb")
, (Text
"yocto", Text -> Exp
str Text
"y")
, (Text
"yotta", Text -> Exp
str Text
"Y")
, (Text
"zepto", Text -> Exp
str Text
"z")
, (Text
"zetta", Text -> Exp
str Text
"Z")
]
where
str :: Text -> Exp
str = TextType -> Text -> Exp
EText TextType
TextNormal
doSInum :: TP Exp
doSInum :: TP Exp
doSInum = do
ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Text () Identity () -> ParsecT Text () Identity ())
-> ParsecT Text () Identity () -> ParsecT Text () Identity ()
forall a b. (a -> b) -> a -> b
$ TP Exp -> ParsecT Text () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TP Exp
inbrackets
TP Exp -> TP Exp
forall a. TP a -> TP a
braces TP Exp
siNum
siNum :: TP Exp
siNum :: TP Exp
siNum = [Exp] -> Exp
asGroup ([Exp] -> Exp) -> (ArrayLine -> [Exp]) -> ArrayLine -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayLine -> [Exp]
forall a. Monoid a => [a] -> a
mconcat (ArrayLine -> Exp) -> TP ArrayLine -> TP Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parsec Text () [Exp] -> TP ArrayLine
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many Parsec Text () [Exp]
parseNumPart
parseNumPart :: TP [Exp]
parseNumPart :: Parsec Text () [Exp]
parseNumPart =
Parsec Text () [Exp]
forall u. ParsecT Text u Identity [Exp]
parseDecimalNum Parsec Text () [Exp]
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () [Exp]
forall u. ParsecT Text u Identity [Exp]
parseComma Parsec Text () [Exp]
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () [Exp]
forall u. ParsecT Text u Identity [Exp]
parsePlusMinus Parsec Text () [Exp]
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () [Exp]
forall u. ParsecT Text u Identity [Exp]
parseI Parsec Text () [Exp]
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () [Exp]
forall u. ParsecT Text u Identity [Exp]
parseExp Parsec Text () [Exp]
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () [Exp]
forall u. ParsecT Text u Identity [Exp]
parseX Parsec Text () [Exp]
-> Parsec Text () [Exp] -> Parsec Text () [Exp]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Parsec Text () [Exp]
forall u. ParsecT Text u Identity [Exp]
parseSpace
where
parseDecimalNum :: ParsecT Text u Identity [Exp]
parseDecimalNum = do
Text
pref <- Text
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty (ParsecT Text u Identity Text -> ParsecT Text u Identity Text)
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall a b. (a -> b) -> a -> b
$ (Text
forall a. Monoid a => a
mempty Text
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'+') ParsecT Text u Identity Text
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text
"\x2212" Text
-> ParsecT Text u Identity Char -> ParsecT Text u Identity Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'-')
Text
basenum <- (Text
pref Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (SourceName -> Text) -> SourceName -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceName -> Text
T.pack
(SourceName -> Text)
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text u Identity Char -> ParsecT Text u Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool) -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> Bool
isDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'))
Text
uncertainty <- Text
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
forall a. Monoid a => a
mempty (ParsecT Text u Identity Text -> ParsecT Text u Identity Text)
-> ParsecT Text u Identity Text -> ParsecT Text u Identity Text
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack (SourceName -> Text)
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text u Identity SourceName
forall u. ParsecT Text u Identity SourceName
parseParens
if Text -> Bool
T.null Text
uncertainty
then [Exp] -> ParsecT Text u Identity [Exp]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text -> Exp
ENumber Text
basenum]
else [Exp] -> ParsecT Text u Identity [Exp]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text -> Exp
ENumber (Text -> Exp) -> Text -> Exp
forall a b. (a -> b) -> a -> b
$ Text
basenum Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\xa0\xb1\xa0" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
let (Text
_,Text
ys) = (Char -> Bool) -> Text -> (Text, Text)
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'.') Text
basenum
in case (Text -> Line
T.length Text
ys Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
1, Text -> Line
T.length Text
uncertainty) of
(Line
0,Line
_) -> Text
uncertainty
(Line
x,Line
y)
| Line
x Line -> Line -> Bool
forall a. Ord a => a -> a -> Bool
> Line
y -> Text
"0." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Line -> Text -> Text
T.replicate (Line
x Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
y) Text
"0" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
(Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'0') Text
uncertainty
| Bool
otherwise -> Line -> Text -> Text
T.take (Line
y Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
x) Text
uncertainty Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
case (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'0')
(Line -> Text -> Text
T.drop (Line
y Line -> Line -> Line
forall a. Num a => a -> a -> a
- Line
x) Text
uncertainty) of
Text
t | Text -> Bool
T.null Text
t -> Text
forall a. Monoid a => a
mempty
| Bool
otherwise -> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t]
parseComma :: ParsecT Text u Identity [Exp]
parseComma = [Text -> Exp
ENumber Text
"."] [Exp]
-> ParsecT Text u Identity Char -> ParsecT Text u Identity [Exp]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
','
parsePlusMinus :: ParsecT Text u Identity [Exp]
parsePlusMinus = [TextType -> Text -> Exp
EText TextType
TextNormal Text
"\xa0\xb1\xa0"] [Exp]
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity [Exp]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT Text u Identity SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"+-")
parseParens :: ParsecT Text u Identity SourceName
parseParens =
Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'(' ParsecT Text u Identity Char
-> ParsecT Text u Identity SourceName
-> ParsecT Text u Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text u Identity Char -> ParsecT Text u Identity SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool) -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> Bool
isDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.')) ParsecT Text u Identity SourceName
-> ParsecT Text u Identity Char
-> ParsecT Text u Identity SourceName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')'
parseI :: ParsecT Text u Identity [Exp]
parseI = [Text -> Exp
EIdentifier Text
"i"] [Exp]
-> ParsecT Text u Identity Char -> ParsecT Text u Identity [Exp]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'i'
parseX :: ParsecT Text u Identity [Exp]
parseX = [TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\xa0\xd7\xa0"] [Exp]
-> ParsecT Text u Identity Char -> ParsecT Text u Identity [Exp]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'x'
parseExp :: ParsecT Text u Identity [Exp]
parseExp = do
Exp
n <- [Exp] -> Exp
asGroup ([Exp] -> Exp)
-> ParsecT Text u Identity [Exp] -> ParsecT Text u Identity Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'e' ParsecT Text u Identity Char
-> ParsecT Text u Identity [Exp] -> ParsecT Text u Identity [Exp]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text u Identity [Exp]
forall u. ParsecT Text u Identity [Exp]
parseDecimalNum)
[Exp] -> ParsecT Text u Identity [Exp]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Exp] -> ParsecT Text u Identity [Exp])
-> [Exp] -> ParsecT Text u Identity [Exp]
forall a b. (a -> b) -> a -> b
$ [TeXSymbolType -> Text -> Exp
ESymbol TeXSymbolType
Rel Text
"\xa0\xd7\xa0", Exp -> Exp -> Exp
ESuper (Text -> Exp
ENumber Text
"10") Exp
n ]
parseSpace :: ParsecT Text u Identity [Exp]
parseSpace = [Exp]
forall a. Monoid a => a
mempty [Exp]
-> ParsecT Text u Identity () -> ParsecT Text u Identity [Exp]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text u Identity Char -> ParsecT Text u Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 (Char -> ParsecT Text u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
' ')