{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.TeXMath.Unicode.ToTeX ( getTeXMath
, getSymbolType
, symbolMap
, records
) where
import qualified Data.Map as M
import qualified Data.Text as T
import Text.TeXMath.TeX
import Text.TeXMath.Types
import Data.Maybe (fromMaybe, listToMaybe, mapMaybe)
import Control.Applicative hiding (optional)
import Text.TeXMath.Unicode.ToUnicode (fromUnicodeChar)
import qualified Text.TeXMath.Shared as S
getTeXMath :: T.Text -> Env -> [TeX]
getTeXMath :: Text -> Env -> [TeX]
getTeXMath Text
s Env
e = (Char -> [TeX]) -> [Char] -> [TeX]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Env -> Char -> [TeX]
charToString Env
e) ([Char] -> [TeX]) -> [Char] -> [TeX]
forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
s
commandTypes :: [TeXSymbolType]
commandTypes :: [TeXSymbolType]
commandTypes = [TeXSymbolType
Accent, TeXSymbolType
Rad, TeXSymbolType
TOver, TeXSymbolType
TUnder]
charToString :: Env -> Char -> [TeX]
charToString :: Env -> Char -> [TeX]
charToString Env
e Char
c =
[TeX] -> Maybe [TeX] -> [TeX]
forall a. a -> Maybe a -> a
fromMaybe [Char -> TeX
escapeLaTeX Char
c]
(Env -> Char -> Maybe [TeX]
charToLaTeXString Env
e Char
c Maybe [TeX] -> Maybe [TeX] -> Maybe [TeX]
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Env -> Char -> Maybe [TeX]
textConvert Env
e Char
c)
charToLaTeXString :: Env -> Char -> Maybe [TeX]
charToLaTeXString :: Env -> Char -> Maybe [TeX]
charToLaTeXString Env
_ Char
'\65024' = [TeX] -> Maybe [TeX]
forall a. a -> Maybe a
Just []
charToLaTeXString Env
environment Char
c = do
Record
v <- Char -> Map Char Record -> Maybe Record
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Char
c Map Char Record
recordsMap
let toLit :: Text -> [TeX]
toLit Text
cs = case Text -> Maybe (Char, Text)
T.uncons Text
cs of
Just (Char
x, Text
xs) -> if Text -> Bool
T.null Text
xs then [Char -> TeX
Token Char
x] else [Text -> TeX
Literal Text
cs]
Maybe (Char, Text)
Nothing -> []
let cmds :: [(Text, Text)]
cmds = Record -> [(Text, Text)]
commands Record
v
Text
raw <- Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"base" [(Text, Text)]
cmds Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Env -> Maybe Text
forall a. [a] -> Maybe a
listToMaybe ((Text -> Maybe Text) -> Env -> Env
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ((Text -> [(Text, Text)] -> Maybe Text)
-> [(Text, Text)] -> Text -> Maybe Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [(Text, Text)]
cmds) Env
environment)
let latexCommand :: [TeX]
latexCommand = if Text -> Bool
isControlSeq Text
raw
then [Text -> TeX
ControlSeq Text
raw]
else Text -> [TeX]
toLit Text
raw
[TeX] -> Maybe [TeX]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return ([TeX] -> Maybe [TeX]) -> [TeX] -> Maybe [TeX]
forall a b. (a -> b) -> a -> b
$ if Record -> TeXSymbolType
category Record
v TeXSymbolType -> [TeXSymbolType] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [TeXSymbolType]
commandTypes
then [TeX]
latexCommand [TeX] -> [TeX] -> [TeX]
forall a. [a] -> [a] -> [a]
++ [[TeX] -> TeX
Grouped []]
else [TeX]
latexCommand
textConvert :: Env -> Char -> Maybe [TeX]
textConvert :: Env -> Char -> Maybe [TeX]
textConvert Env
env Char
c = do
(TextType
ttype, Char
v) <- Char -> Maybe (TextType, Char)
fromUnicodeChar Char
c
[TeX] -> Maybe [TeX]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text -> TeX
ControlSeq (Env -> TextType -> Text
S.getLaTeXTextCommand Env
env TextType
ttype), [TeX] -> TeX
Grouped [Char -> TeX
Token Char
v]]
recordsMap :: M.Map Char Record
recordsMap :: Map Char Record
recordsMap = [(Char, Record)] -> Map Char Record
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ((Record -> (Char, Record)) -> [Record] -> [(Char, Record)]
forall a b. (a -> b) -> [a] -> [b]
map Record -> (Char, Record)
f [Record]
records)
where
f :: Record -> (Char, Record)
f Record
r = (Record -> Char
uchar Record
r, Record
r)
getSymbolType :: Char -> TeXSymbolType
getSymbolType :: Char -> TeXSymbolType
getSymbolType Char
c = TeXSymbolType -> Maybe TeXSymbolType -> TeXSymbolType
forall a. a -> Maybe a -> a
fromMaybe TeXSymbolType
Ord (Record -> TeXSymbolType
category (Record -> TeXSymbolType) -> Maybe Record -> Maybe TeXSymbolType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> Map Char Record -> Maybe Record
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Char
c Map Char Record
recordsMap)
symbolMap :: M.Map T.Text Exp
symbolMap :: Map Text Exp
symbolMap = (Record -> Map Text Exp -> Map Text Exp)
-> Map Text Exp -> [Record] -> Map Text Exp
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Record -> Map Text Exp -> Map Text Exp
go Map Text Exp
forall a. Monoid a => a
mempty [Record]
records
where
go :: Record -> Map Text Exp -> Map Text Exp
go Record
r Map Text Exp
m =
((Text, Text) -> Map Text Exp -> Map Text Exp)
-> Map Text Exp -> [(Text, Text)] -> Map Text Exp
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(Text
_,!Text
c) ->
if Int -> Text -> Text
T.take Int
1 Text
c Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\\" Bool -> Bool -> Bool
&& Bool -> Bool
not ((Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'{') Text
c)
then
let !t :: Text
t = Char -> Text
T.singleton (Char -> Text) -> Char -> Text
forall a b. (a -> b) -> a -> b
$! Record -> Char
uchar (Record -> Char) -> Record -> Char
forall a b. (a -> b) -> a -> b
$! Record
r
in Text -> Exp -> Map Text Exp -> Map Text Exp
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
c (TeXSymbolType -> Text -> Exp
ESymbol (Record -> TeXSymbolType
category Record
r) Text
t)
else Map Text Exp -> Map Text Exp
forall a. a -> a
id)
Map Text Exp
m
(Record -> [(Text, Text)]
commands Record
r)
records :: [Record]
records :: [Record]
records =
[ Record {uchar :: Char
uchar = Char
'!', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"!"),(Text
"unicode-math",Text
"\\exclam")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = Text
"EXCLAMATION MARK"}
, Record {uchar :: Char
uchar = Char
'#', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\#"),(Text
"oz",Text
"\\#"),(Text
"unicode-math",Text
"\\octothorpe")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NUMBER SIGN"}
, Record {uchar :: Char
uchar = Char
'$', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\$"),(Text
"base",Text
"\\mathdollar"),(Text
"unicode-math",Text
"\\mathdollar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOLLAR SIGN"}
, Record {uchar :: Char
uchar = Char
'%', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\%"),(Text
"unicode-math",Text
"\\percent")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PERCENT SIGN"}
, Record {uchar :: Char
uchar = Char
'&', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\&"),(Text
"stmaryrd",Text
"\\binampersand"),(Text
"unicode-math",Text
"\\ampersand")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
""}
, Record {uchar :: Char
uchar = Char
'(', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"("),(Text
"unicode-math",Text
"\\lparen")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT PARENTHESIS"}
, Record {uchar :: Char
uchar = Char
')', commands :: [(Text, Text)]
commands = [(Text
"base",Text
")"),(Text
"unicode-math",Text
"\\rparen")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT PARENTHESIS"}
, Record {uchar :: Char
uchar = Char
'*', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"*"),(Text
"base",Text
"\\ast")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"(high) ASTERISK, star"}
, Record {uchar :: Char
uchar = Char
'+', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"+"),(Text
"unicode-math",Text
"\\plus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN"}
, Record {uchar :: Char
uchar = Char
',', commands :: [(Text, Text)]
commands = [(Text
"base",Text
","),(Text
"unicode-math",Text
"\\comma")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = Text
"COMMA"}
, Record {uchar :: Char
uchar = Char
'-', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"-")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"t -, HYPHEN-MINUS (deprecated for math)"}
, Record {uchar :: Char
uchar = Char
'.', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"."),(Text
"unicode-math",Text
"\\period")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"FULL STOP, period"}
, Record {uchar :: Char
uchar = Char
'/', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"/"),(Text
"base",Text
"\\slash"),(Text
"unicode-math",Text
"\\mathslash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SOLIDUS"}
, Record {uchar :: Char
uchar = Char
'0', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"0")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT ZERO"}
, Record {uchar :: Char
uchar = Char
'1', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"1")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT ONE"}
, Record {uchar :: Char
uchar = Char
'2', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"2")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT TWO"}
, Record {uchar :: Char
uchar = Char
'3', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"3")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT THREE"}
, Record {uchar :: Char
uchar = Char
'4', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"4")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT FOUR"}
, Record {uchar :: Char
uchar = Char
'5', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"5")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT FIVE"}
, Record {uchar :: Char
uchar = Char
'6', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"6")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT SIX"}
, Record {uchar :: Char
uchar = Char
'7', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"7")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT SEVEN"}
, Record {uchar :: Char
uchar = Char
'8', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"8")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT EIGHT"}
, Record {uchar :: Char
uchar = Char
'9', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"9")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIGIT NINE"}
, Record {uchar :: Char
uchar = Char
':', commands :: [(Text, Text)]
commands = [(Text
"base",Text
":"),(Text
"literal",Text
"\\colon"),(Text
"unicode-math",Text
"\\mathcolon")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = Text
"COLON (not ratio)"}
, Record {uchar :: Char
uchar = Char
';', commands :: [(Text, Text)]
commands = [(Text
"base",Text
";"),(Text
"unicode-math",Text
"\\semicolon")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = Text
"SEMICOLON p:"}
, Record {uchar :: Char
uchar = Char
'<', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"<"),(Text
"unicode-math",Text
"\\less")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN SIGN r:"}
, Record {uchar :: Char
uchar = Char
'=', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"="),(Text
"unicode-math",Text
"\\equal")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN r:"}
, Record {uchar :: Char
uchar = Char
'>', commands :: [(Text, Text)]
commands = [(Text
"base",Text
">"),(Text
"unicode-math",Text
"\\greater")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN SIGN r:"}
, Record {uchar :: Char
uchar = Char
'?', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"?"),(Text
"unicode-math",Text
"\\question")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"QUESTION MARK"}
, Record {uchar :: Char
uchar = Char
'@', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"@"),(Text
"unicode-math",Text
"\\atsign")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"at"}
, Record {uchar :: Char
uchar = Char
'A', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"A"),(Text
"base",Text
"\\mathrm{A}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER A"}
, Record {uchar :: Char
uchar = Char
'B', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"B"),(Text
"base",Text
"\\mathrm{B}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER B"}
, Record {uchar :: Char
uchar = Char
'C', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"C"),(Text
"base",Text
"\\mathrm{C}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER C"}
, Record {uchar :: Char
uchar = Char
'D', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"D"),(Text
"base",Text
"\\mathrm{D}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER D"}
, Record {uchar :: Char
uchar = Char
'E', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"E"),(Text
"base",Text
"\\mathrm{E}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER E"}
, Record {uchar :: Char
uchar = Char
'F', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"F"),(Text
"base",Text
"\\mathrm{F}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER F"}
, Record {uchar :: Char
uchar = Char
'G', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"G"),(Text
"base",Text
"\\mathrm{G}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER G"}
, Record {uchar :: Char
uchar = Char
'H', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"H"),(Text
"base",Text
"\\mathrm{H}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER H"}
, Record {uchar :: Char
uchar = Char
'I', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"I"),(Text
"base",Text
"\\mathrm{I}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER I"}
, Record {uchar :: Char
uchar = Char
'J', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"J"),(Text
"base",Text
"\\mathrm{J}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER J"}
, Record {uchar :: Char
uchar = Char
'K', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"K"),(Text
"base",Text
"\\mathrm{K}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER K"}
, Record {uchar :: Char
uchar = Char
'L', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"L"),(Text
"base",Text
"\\mathrm{L}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER L"}
, Record {uchar :: Char
uchar = Char
'M', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"M"),(Text
"base",Text
"\\mathrm{M}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER M"}
, Record {uchar :: Char
uchar = Char
'N', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"N"),(Text
"base",Text
"\\mathrm{N}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER N"}
, Record {uchar :: Char
uchar = Char
'O', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"O"),(Text
"base",Text
"\\mathrm{O}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER O"}
, Record {uchar :: Char
uchar = Char
'P', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"P"),(Text
"base",Text
"\\mathrm{P}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER P"}
, Record {uchar :: Char
uchar = Char
'Q', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"Q"),(Text
"base",Text
"\\mathrm{Q}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER Q"}
, Record {uchar :: Char
uchar = Char
'R', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"R"),(Text
"base",Text
"\\mathrm{R}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER R"}
, Record {uchar :: Char
uchar = Char
'S', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"S"),(Text
"base",Text
"\\mathrm{S}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER S"}
, Record {uchar :: Char
uchar = Char
'T', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"T"),(Text
"base",Text
"\\mathrm{T}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER T"}
, Record {uchar :: Char
uchar = Char
'U', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"U"),(Text
"base",Text
"\\mathrm{U}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER U"}
, Record {uchar :: Char
uchar = Char
'V', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"V"),(Text
"base",Text
"\\mathrm{V}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER V"}
, Record {uchar :: Char
uchar = Char
'W', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"W"),(Text
"base",Text
"\\mathrm{W}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER W"}
, Record {uchar :: Char
uchar = Char
'X', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"X"),(Text
"base",Text
"\\mathrm{X}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER X"}
, Record {uchar :: Char
uchar = Char
'Y', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"Y"),(Text
"base",Text
"\\mathrm{Y}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER Y"}
, Record {uchar :: Char
uchar = Char
'Z', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"Z"),(Text
"base",Text
"\\mathrm{Z}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN CAPITAL LETTER Z"}
, Record {uchar :: Char
uchar = Char
'[', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\lbrack"),(Text
"unicode-math",Text
"\\lbrack")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT SQUARE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\\', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\backslash"),(Text
"unicode-math",Text
"\\backslash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"REVERSE SOLIDUS"}
, Record {uchar :: Char
uchar = Char
']', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rbrack"),(Text
"unicode-math",Text
"\\rbrack")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT SQUARE BRACKET"}
, Record {uchar :: Char
uchar = Char
'^', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\hat{}"),(Text
"unicode-math",Text
"\\sphat")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"amsxtra^CIRCUMFLEX ACCENT, TeX superscript operator"}
, Record {uchar :: Char
uchar = Char
'_', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\_")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOW LINE, TeX subscript operator"}
, Record {uchar :: Char
uchar = Char
'`', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"grave, alias for 0300"}
, Record {uchar :: Char
uchar = Char
'a', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"a"),(Text
"base",Text
"\\mathrm{a}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER A"}
, Record {uchar :: Char
uchar = Char
'b', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"b"),(Text
"base",Text
"\\mathrm{b}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER B"}
, Record {uchar :: Char
uchar = Char
'c', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"c"),(Text
"base",Text
"\\mathrm{c}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER C"}
, Record {uchar :: Char
uchar = Char
'd', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"d"),(Text
"base",Text
"\\mathrm{d}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER D"}
, Record {uchar :: Char
uchar = Char
'e', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"e"),(Text
"base",Text
"\\mathrm{e}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER E"}
, Record {uchar :: Char
uchar = Char
'f', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"f"),(Text
"base",Text
"\\mathrm{f}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER F"}
, Record {uchar :: Char
uchar = Char
'g', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"g"),(Text
"base",Text
"\\mathrm{g}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER G"}
, Record {uchar :: Char
uchar = Char
'h', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"h"),(Text
"base",Text
"\\mathrm{h}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER H"}
, Record {uchar :: Char
uchar = Char
'i', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"i"),(Text
"base",Text
"\\mathrm{i}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER I"}
, Record {uchar :: Char
uchar = Char
'j', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"j"),(Text
"base",Text
"\\mathrm{j}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER J"}
, Record {uchar :: Char
uchar = Char
'k', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"k"),(Text
"base",Text
"\\mathrm{k}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER K"}
, Record {uchar :: Char
uchar = Char
'l', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"l"),(Text
"base",Text
"\\mathrm{l}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER L"}
, Record {uchar :: Char
uchar = Char
'm', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"m"),(Text
"base",Text
"\\mathrm{m}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER M"}
, Record {uchar :: Char
uchar = Char
'n', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"n"),(Text
"base",Text
"\\mathrm{n}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER N"}
, Record {uchar :: Char
uchar = Char
'o', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"o"),(Text
"base",Text
"\\mathrm{o}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER O"}
, Record {uchar :: Char
uchar = Char
'p', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"p"),(Text
"base",Text
"\\mathrm{p}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER P"}
, Record {uchar :: Char
uchar = Char
'q', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"q"),(Text
"base",Text
"\\mathrm{q}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER Q"}
, Record {uchar :: Char
uchar = Char
'r', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"r"),(Text
"base",Text
"\\mathrm{r}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER R"}
, Record {uchar :: Char
uchar = Char
's', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"s"),(Text
"base",Text
"\\mathrm{s}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER S"}
, Record {uchar :: Char
uchar = Char
't', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"t"),(Text
"base",Text
"\\mathrm{t}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER T"}
, Record {uchar :: Char
uchar = Char
'u', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"u"),(Text
"base",Text
"\\mathrm{u}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER U"}
, Record {uchar :: Char
uchar = Char
'v', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"v"),(Text
"base",Text
"\\mathrm{v}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER V"}
, Record {uchar :: Char
uchar = Char
'w', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"w"),(Text
"base",Text
"\\mathrm{w}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER W"}
, Record {uchar :: Char
uchar = Char
'x', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"x"),(Text
"base",Text
"\\mathrm{x}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER X"}
, Record {uchar :: Char
uchar = Char
'y', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"y"),(Text
"base",Text
"\\mathrm{y}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER Y"}
, Record {uchar :: Char
uchar = Char
'z', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"z"),(Text
"base",Text
"\\mathrm{z}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"LATIN SMALL LETTER Z"}
, Record {uchar :: Char
uchar = Char
'{', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\{"),(Text
"base",Text
"\\lbrace"),(Text
"unicode-math",Text
"\\lbrace")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT CURLY BRACKET"}
, Record {uchar :: Char
uchar = Char
'|', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"|"),(Text
"base",Text
"\\vert"),(Text
"unicode-math",Text
"\\vert")], category :: TeXSymbolType
category = TeXSymbolType
Fence, comments :: Text
comments = Text
"vertical bar"}
, Record {uchar :: Char
uchar = Char
'}', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\}"),(Text
"base",Text
"\\rbrace"),(Text
"unicode-math",Text
"\\rbrace")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT CURLY BRACKET"}
, Record {uchar :: Char
uchar = Char
'~', commands :: [(Text, Text)]
commands = [(Text
"amsxtra",Text
"\\sptilde"),(Text
"base",Text
"\\sim")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TILDE"}
, Record {uchar :: Char
uchar = Char
'\160', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"~")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"nbsp"}
, Record {uchar :: Char
uchar = Char
'\161', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"iexcl"}
, Record {uchar :: Char
uchar = Char
'\162', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\cent"),(Text
"txfonts",Text
"\\mathcent")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"cent"}
, Record {uchar :: Char
uchar = Char
'\163', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\pounds"),(Text
"txfonts",Text
"\\mathsterling"),(Text
"unicode-math",Text
"\\sterling")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"POUND SIGN, fourier prints a dollar sign"}
, Record {uchar :: Char
uchar = Char
'\164', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"t \\currency (wasysym), curren"}
, Record {uchar :: Char
uchar = Char
'\165', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\yen"),(Text
"unicode-math",Text
"\\yen")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"YEN SIGN"}
, Record {uchar :: Char
uchar = Char
'\166', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"brvbar (vertical)"}
, Record {uchar :: Char
uchar = Char
'\167', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"sect"}
, Record {uchar :: Char
uchar = Char
'\168', commands :: [(Text, Text)]
commands = [(Text
"amsxtra",Text
"\\spddot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"Dot /die, alias for 0308"}
, Record {uchar :: Char
uchar = Char
'\172', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\neg"),(Text
"base",Text
"\\lnot"),(Text
"unicode-math",Text
"\\neg")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NOT SIGN"}
, Record {uchar :: Char
uchar = Char
'\174', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\circledR")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"REGISTERED SIGN"}
, Record {uchar :: Char
uchar = Char
'\175', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"macr, alias for 0304"}
, Record {uchar :: Char
uchar = Char
'\176', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"{^\\circ}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"deg"}
, Record {uchar :: Char
uchar = Char
'\177', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\pm"),(Text
"unicode-math",Text
"\\pm")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"plus-or-minus sign"}
, Record {uchar :: Char
uchar = Char
'\178', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"sup2"}
, Record {uchar :: Char
uchar = Char
'\179', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"sup3"}
, Record {uchar :: Char
uchar = Char
'\180', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"acute, alias for 0301"}
, Record {uchar :: Char
uchar = Char
'\181', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\Micro"),(Text
"mathcomp",Text
"\\tcmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"t \\textmu (textcomp), # \\mathrm{\\mu} (omlmathrm), # \\muup (kpfonts mathdesign), MICRO SIGN"}
, Record {uchar :: Char
uchar = Char
'\182', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"para (paragraph sign, pilcrow)"}
, Record {uchar :: Char
uchar = Char
'\183', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\cdot"),(Text
"unicode-math",Text
"\\cdotp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"x \\centerdot, b: MIDDLE DOT"}
, Record {uchar :: Char
uchar = Char
'\185', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"sup1"}
, Record {uchar :: Char
uchar = Char
'\188', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"frac14"}
, Record {uchar :: Char
uchar = Char
'\189', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"frac12"}
, Record {uchar :: Char
uchar = Char
'\190', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"frac34"}
, Record {uchar :: Char
uchar = Char
'\191', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"iquest"}
, Record {uchar :: Char
uchar = Char
'\215', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\times"),(Text
"unicode-math",Text
"\\times")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTIPLICATION SIGN, z notation Cartesian product"}
, Record {uchar :: Char
uchar = Char
'\240', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\eth"),(Text
"arevmath",Text
"\\eth"),(Text
"unicode-math",Text
"\\matheth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"eth"}
, Record {uchar :: Char
uchar = Char
'\247', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\div"),(Text
"unicode-math",Text
"\\div")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"divide sign"}
, Record {uchar :: Char
uchar = Char
'\305', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\imath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"imath"}
, Record {uchar :: Char
uchar = Char
'\437', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Zbar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"impedance"}
, Record {uchar :: Char
uchar = Char
'\567', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\jmath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"jmath"}
, Record {uchar :: Char
uchar = Char
'\710', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\hat{}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"circ, alias for 0302"}
, Record {uchar :: Char
uchar = Char
'\711', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"CARON, alias for 030C"}
, Record {uchar :: Char
uchar = Char
'\728', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BREVE, alias for 0306"}
, Record {uchar :: Char
uchar = Char
'\729', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"dot, alias for 0307"}
, Record {uchar :: Char
uchar = Char
'\730', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ring, alias for 030A"}
, Record {uchar :: Char
uchar = Char
'\732', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"tilde, alias for 0303"}
, Record {uchar :: Char
uchar = Char
'\768', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\grave"),(Text
"unicode-math",Text
"\\grave")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"grave accent"}
, Record {uchar :: Char
uchar = Char
'\769', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\acute"),(Text
"unicode-math",Text
"\\acute")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"acute accent"}
, Record {uchar :: Char
uchar = Char
'\770', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\hat"),(Text
"amssymb",Text
"\\widehat"),(Text
"unicode-math",Text
"\\hat")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"circumflex accent"}
, Record {uchar :: Char
uchar = Char
'\771', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\tilde"),(Text
"yhmath, fourier",Text
"\\widetilde"),(Text
"unicode-math",Text
"\\tilde")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"tilde"}
, Record {uchar :: Char
uchar = Char
'\772', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bar"),(Text
"unicode-math",Text
"\\bar")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"macron"}
, Record {uchar :: Char
uchar = Char
'\773', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\overline"),(Text
"unicode-math",Text
"\\overbar")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"overbar embellishment"}
, Record {uchar :: Char
uchar = Char
'\774', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\breve"),(Text
"unicode-math",Text
"\\breve")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"breve"}
, Record {uchar :: Char
uchar = Char
'\775', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\dot"),(Text
"wrisym",Text
"\\Dot"),(Text
"unicode-math",Text
"\\dot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"dot above"}
, Record {uchar :: Char
uchar = Char
'\776', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ddot"),(Text
"wrisym",Text
"\\DDot"),(Text
"unicode-math",Text
"\\ddot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"dieresis"}
, Record {uchar :: Char
uchar = Char
'\777', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ovhook")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING HOOK ABOVE"}
, Record {uchar :: Char
uchar = Char
'\778', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\mathring"),(Text
"yhmath",Text
"\\ring"),(Text
"unicode-math",Text
"\\ocirc")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"ring"}
, Record {uchar :: Char
uchar = Char
'\780', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\check"),(Text
"unicode-math",Text
"\\check")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"caron"}
, Record {uchar :: Char
uchar = Char
'\784', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\candra")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"candrabindu (non-spacing)"}
, Record {uchar :: Char
uchar = Char
'\785', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING INVERTED BREVE"}
, Record {uchar :: Char
uchar = Char
'\786', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\oturnedcomma")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING TURNED COMMA ABOVE"}
, Record {uchar :: Char
uchar = Char
'\789', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ocommatopright")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING COMMA ABOVE RIGHT"}
, Record {uchar :: Char
uchar = Char
'\794', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\droang")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"left angle above (non-spacing)"}
, Record {uchar :: Char
uchar = Char
'\803', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING DOT BELOW"}
, Record {uchar :: Char
uchar = Char
'\812', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING CARON BELOW"}
, Record {uchar :: Char
uchar = Char
'\813', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING CIRCUMFLEX ACCENT BELOW"}
, Record {uchar :: Char
uchar = Char
'\814', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING BREVE BELOW"}
, Record {uchar :: Char
uchar = Char
'\815', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING INVERTED BREVE BELOW"}
, Record {uchar :: Char
uchar = Char
'\816', commands :: [(Text, Text)]
commands = [(Text
"undertilde",Text
"\\utilde"),(Text
"unicode-math",Text
"\\wideutilde")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"under tilde accent (multiple characters and non-spacing)"}
, Record {uchar :: Char
uchar = Char
'\817', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\underbar"),(Text
"unicode-math",Text
"\\underbar")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING MACRON BELOW"}
, Record {uchar :: Char
uchar = Char
'\818', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\underline")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LOW LINE"}
, Record {uchar :: Char
uchar = Char
'\819', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"2lowbar"}
, Record {uchar :: Char
uchar = Char
'\824', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\not"),(Text
"unicode-math",Text
"\\not")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LONG SOLIDUS OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\826', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING INVERTED BRIDGE BELOW"}
, Record {uchar :: Char
uchar = Char
'\831', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING DOUBLE OVERLINE"}
, Record {uchar :: Char
uchar = Char
'\838', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING BRIDGE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\913', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital alpha, greek"}
, Record {uchar :: Char
uchar = Char
'\914', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital beta, greek"}
, Record {uchar :: Char
uchar = Char
'\915', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Gamma"),(Text
"-slantedGreek",Text
"\\Gamma"),(Text
"unicode-math",Text
"\\upGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Gamma}, capital gamma, greek"}
, Record {uchar :: Char
uchar = Char
'\916', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Delta"),(Text
"-slantedGreek",Text
"\\Delta"),(Text
"unicode-math",Text
"\\upDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Delta}, capital delta, greek"}
, Record {uchar :: Char
uchar = Char
'\917', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital epsilon, greek"}
, Record {uchar :: Char
uchar = Char
'\918', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital zeta, greek"}
, Record {uchar :: Char
uchar = Char
'\919', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital eta, greek"}
, Record {uchar :: Char
uchar = Char
'\920', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Theta"),(Text
"-slantedGreek",Text
"\\Theta"),(Text
"unicode-math",Text
"\\upTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Theta}, capital theta, greek"}
, Record {uchar :: Char
uchar = Char
'\921', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital iota, greek"}
, Record {uchar :: Char
uchar = Char
'\922', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital kappa, greek"}
, Record {uchar :: Char
uchar = Char
'\923', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Lambda"),(Text
"-slantedGreek",Text
"\\Lambda"),(Text
"unicode-math",Text
"\\upLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Lambda}, capital lambda, greek"}
, Record {uchar :: Char
uchar = Char
'\924', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital mu, greek"}
, Record {uchar :: Char
uchar = Char
'\925', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital nu, greek"}
, Record {uchar :: Char
uchar = Char
'\926', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Xi"),(Text
"-slantedGreek",Text
"\\Xi"),(Text
"unicode-math",Text
"\\upXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Xi}, capital xi, greek"}
, Record {uchar :: Char
uchar = Char
'\927', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital omicron, greek"}
, Record {uchar :: Char
uchar = Char
'\928', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Pi"),(Text
"-slantedGreek",Text
"\\Pi"),(Text
"unicode-math",Text
"\\upPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Pi}, capital pi, greek"}
, Record {uchar :: Char
uchar = Char
'\929', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital rho, greek"}
, Record {uchar :: Char
uchar = Char
'\931', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Sigma"),(Text
"-slantedGreek",Text
"\\Sigma"),(Text
"unicode-math",Text
"\\upSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Sigma}, capital sigma, greek"}
, Record {uchar :: Char
uchar = Char
'\932', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital tau, greek"}
, Record {uchar :: Char
uchar = Char
'\933', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Upsilon"),(Text
"-slantedGreek",Text
"\\Upsilon"),(Text
"unicode-math",Text
"\\upUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Upsilon}, capital upsilon, greek"}
, Record {uchar :: Char
uchar = Char
'\934', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Phi"),(Text
"-slantedGreek",Text
"\\Phi"),(Text
"unicode-math",Text
"\\upPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Phi}, capital phi, greek"}
, Record {uchar :: Char
uchar = Char
'\935', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital chi, greek"}
, Record {uchar :: Char
uchar = Char
'\936', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Psi"),(Text
"-slantedGreek",Text
"\\Psi"),(Text
"unicode-math",Text
"\\upPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Psi}, capital psi, greek"}
, Record {uchar :: Char
uchar = Char
'\937', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Omega"),(Text
"-slantedGreek",Text
"\\Omega"),(Text
"unicode-math",Text
"\\upOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\mathrm{\\Omega}, capital omega, greek"}
, Record {uchar :: Char
uchar = Char
'\945', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\alpha"),(Text
"omlmathrm",Text
"\\mathrm{\\alpha}"),(Text
"unicode-math",Text
"\\upalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\alphaup (kpfonts mathdesign), = \\upalpha (upgreek), alpha, greek"}
, Record {uchar :: Char
uchar = Char
'\946', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\beta"),(Text
"omlmathrm",Text
"\\mathrm{\\beta}"),(Text
"unicode-math",Text
"\\upbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\betaup (kpfonts mathdesign), = \\upbeta (upgreek), beta, greek"}
, Record {uchar :: Char
uchar = Char
'\947', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\gamma"),(Text
"omlmathrm",Text
"\\mathrm{\\gamma}"),(Text
"unicode-math",Text
"\\upgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\gammaup (kpfonts mathdesign), = \\upgamma (upgreek), gamma, greek"}
, Record {uchar :: Char
uchar = Char
'\948', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\delta"),(Text
"omlmathrm",Text
"\\mathrm{\\delta}"),(Text
"unicode-math",Text
"\\updelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\deltaup (kpfonts mathdesign), = \\updelta (upgreek), delta, greek"}
, Record {uchar :: Char
uchar = Char
'\949', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varepsilon"),(Text
"omlmathrm",Text
"\\mathrm{\\varepsilon}"),(Text
"unicode-math",Text
"\\upepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varepsilonup (kpfonts mathdesign), = \\upepsilon (upgreek), rounded epsilon, greek"}
, Record {uchar :: Char
uchar = Char
'\950', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\zeta"),(Text
"omlmathrm",Text
"\\mathrm{\\zeta}"),(Text
"unicode-math",Text
"\\upzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\zetaup (kpfonts mathdesign), = \\upzeta (upgreek), zeta, greek"}
, Record {uchar :: Char
uchar = Char
'\951', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\eta"),(Text
"omlmathrm",Text
"\\mathrm{\\eta}"),(Text
"unicode-math",Text
"\\upeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\etaup (kpfonts mathdesign), = \\upeta (upgreek), eta, greek"}
, Record {uchar :: Char
uchar = Char
'\952', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\theta"),(Text
"omlmathrm",Text
"\\mathrm{\\theta}"),(Text
"unicode-math",Text
"\\uptheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\thetaup (kpfonts mathdesign), straight theta, = \\uptheta (upgreek), theta, greek"}
, Record {uchar :: Char
uchar = Char
'\953', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\iota"),(Text
"omlmathrm",Text
"\\mathrm{\\iota}"),(Text
"unicode-math",Text
"\\upiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\iotaup (kpfonts mathdesign), = \\upiota (upgreek), iota, greek"}
, Record {uchar :: Char
uchar = Char
'\954', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\kappa"),(Text
"omlmathrm",Text
"\\mathrm{\\kappa}"),(Text
"unicode-math",Text
"\\upkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\kappaup (kpfonts mathdesign), = \\upkappa (upgreek), kappa, greek"}
, Record {uchar :: Char
uchar = Char
'\955', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\lambda"),(Text
"omlmathrm",Text
"\\mathrm{\\lambda}"),(Text
"unicode-math",Text
"\\uplambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\lambdaup (kpfonts mathdesign), = \\uplambda (upgreek), lambda, greek"}
, Record {uchar :: Char
uchar = Char
'\956', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mu"),(Text
"omlmathrm",Text
"\\mathrm{\\mu}"),(Text
"unicode-math",Text
"\\upmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\muup (kpfonts mathdesign), = \\upmu (upgreek), mu, greek"}
, Record {uchar :: Char
uchar = Char
'\957', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\nu"),(Text
"omlmathrm",Text
"\\mathrm{\\nu}"),(Text
"unicode-math",Text
"\\upnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\nuup (kpfonts mathdesign), = \\upnu (upgreek), nu, greek"}
, Record {uchar :: Char
uchar = Char
'\958', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\xi"),(Text
"omlmathrm",Text
"\\mathrm{\\xi}"),(Text
"unicode-math",Text
"\\upxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\xiup (kpfonts mathdesign), = \\upxi (upgreek), xi, greek"}
, Record {uchar :: Char
uchar = Char
'\959', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"small omicron, greek"}
, Record {uchar :: Char
uchar = Char
'\960', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\pi"),(Text
"omlmathrm",Text
"\\mathrm{\\pi}"),(Text
"unicode-math",Text
"\\uppi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\piup (kpfonts mathdesign), = \\uppi (upgreek), pi, greek"}
, Record {uchar :: Char
uchar = Char
'\961', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rho"),(Text
"omlmathrm",Text
"\\mathrm{\\rho}"),(Text
"unicode-math",Text
"\\uprho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\rhoup (kpfonts mathdesign), = \\uprho (upgreek), rho, greek"}
, Record {uchar :: Char
uchar = Char
'\962', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varsigma"),(Text
"omlmathrm",Text
"\\mathrm{\\varsigma}"),(Text
"unicode-math",Text
"\\upvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varsigmaup (kpfonts mathdesign), = \\upvarsigma (upgreek), terminal sigma, greek"}
, Record {uchar :: Char
uchar = Char
'\963', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sigma"),(Text
"omlmathrm",Text
"\\mathrm{\\sigma}"),(Text
"unicode-math",Text
"\\upsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\sigmaup (kpfonts mathdesign), = \\upsigma (upgreek), sigma, greek"}
, Record {uchar :: Char
uchar = Char
'\964', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\tau"),(Text
"omlmathrm",Text
"\\mathrm{\\tau}"),(Text
"unicode-math",Text
"\\uptau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\tauup (kpfonts mathdesign), = \\uptau (upgreek), tau, greek"}
, Record {uchar :: Char
uchar = Char
'\965', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\upsilon"),(Text
"omlmathrm",Text
"\\mathrm{\\upsilon}"),(Text
"unicode-math",Text
"\\upupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\upsilonup (kpfonts mathdesign), = \\upupsilon (upgreek), upsilon, greek"}
, Record {uchar :: Char
uchar = Char
'\966', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varphi"),(Text
"omlmathrm",Text
"\\mathrm{\\varphi}"),(Text
"unicode-math",Text
"\\upvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varphiup (kpfonts mathdesign), = \\upvarphi (upgreek), curly or open phi, greek"}
, Record {uchar :: Char
uchar = Char
'\967', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\chi"),(Text
"omlmathrm",Text
"\\mathrm{\\chi}"),(Text
"unicode-math",Text
"\\upchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\chiup (kpfonts mathdesign), = \\upchi (upgreek), chi, greek"}
, Record {uchar :: Char
uchar = Char
'\968', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\psi"),(Text
"omlmathrm",Text
"\\mathrm{\\psi}"),(Text
"unicode-math",Text
"\\uppsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\psiup (kpfonts mathdesign), = \\uppsi (upgreek), psi, greek"}
, Record {uchar :: Char
uchar = Char
'\969', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\omega"),(Text
"omlmathrm",Text
"\\mathrm{\\omega}"),(Text
"unicode-math",Text
"\\upomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\omegaup (kpfonts mathdesign), = \\upomega (upgreek), omega, greek"}
, Record {uchar :: Char
uchar = Char
'\976', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\varbeta"),(Text
"unicode-math",Text
"\\upvarbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"rounded beta, greek"}
, Record {uchar :: Char
uchar = Char
'\977', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\vartheta"),(Text
"omlmathrm",Text
"\\mathrm{\\vartheta}"),(Text
"unicode-math",Text
"\\upvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varthetaup (kpfonts mathdesign), curly or open theta"}
, Record {uchar :: Char
uchar = Char
'\978', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathrm{\\Upsilon}"),(Text
"unicode-math",Text
"\\upUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"GREEK UPSILON WITH HOOK SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\981', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\phi"),(Text
"omlmathrm",Text
"\\mathrm{\\phi}"),(Text
"unicode-math",Text
"\\upphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\phiup (kpfonts mathdesign), GREEK PHI SYMBOL (straight)"}
, Record {uchar :: Char
uchar = Char
'\982', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varpi"),(Text
"omlmathrm",Text
"\\mathrm{\\varpi}"),(Text
"unicode-math",Text
"\\upvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varpiup (kpfonts mathdesign), GREEK PI SYMBOL (pomega)"}
, Record {uchar :: Char
uchar = Char
'\984', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\Qoppa"),(Text
"wrisym",Text
"\\Koppa"),(Text
"unicode-math",Text
"\\upoldKoppa")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"t \\Qoppa (LGR), GREEK LETTER ARCHAIC KOPPA"}
, Record {uchar :: Char
uchar = Char
'\985', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\qoppa"),(Text
"wrisym",Text
"\\koppa"),(Text
"unicode-math",Text
"\\upoldkoppa")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"t \\qoppa (LGR), GREEK SMALL LETTER ARCHAIC KOPPA"}
, Record {uchar :: Char
uchar = Char
'\986', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\Stigma"),(Text
"wrisym",Text
"\\Stigma"),(Text
"unicode-math",Text
"\\upStigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital stigma"}
, Record {uchar :: Char
uchar = Char
'\987', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\stigma"),(Text
"wrisym",Text
"\\stigma"),(Text
"unicode-math",Text
"\\upstigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"GREEK SMALL LETTER STIGMA"}
, Record {uchar :: Char
uchar = Char
'\988', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\Digamma"),(Text
"amssymb",Text
"\\digamma"),(Text
"unicode-math",Text
"\\upDigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital digamma"}
, Record {uchar :: Char
uchar = Char
'\989', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\digamma"),(Text
"wrisym",Text
"\\digamma"),(Text
"unicode-math",Text
"\\updigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"GREEK SMALL LETTER DIGAMMA"}
, Record {uchar :: Char
uchar = Char
'\990', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\Koppa"),(Text
"unicode-math",Text
"\\upKoppa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital koppa"}
, Record {uchar :: Char
uchar = Char
'\991', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\koppa"),(Text
"unicode-math",Text
"\\upkoppa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"GREEK SMALL LETTER KOPPA"}
, Record {uchar :: Char
uchar = Char
'\992', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\Sampi"),(Text
"wrisym",Text
"\\Sampi"),(Text
"unicode-math",Text
"\\upSampi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"capital sampi"}
, Record {uchar :: Char
uchar = Char
'\993', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\sampi"),(Text
"wrisym",Text
"\\sampi"),(Text
"unicode-math",Text
"\\upsampi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"GREEK SMALL LETTER SAMPI"}
, Record {uchar :: Char
uchar = Char
'\1008', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"GREEK KAPPA SYMBOL (round)"}
, Record {uchar :: Char
uchar = Char
'\1009', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varrho"),(Text
"omlmathrm",Text
"\\mathrm{\\varrho}"),(Text
"unicode-math",Text
"\\upvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varrhoup (kpfonts mathdesign), GREEK RHO SYMBOL (round)"}
, Record {uchar :: Char
uchar = Char
'\1012', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"x \\varTheta (amssymb), GREEK CAPITAL THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\1013', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\epsilon"),(Text
"omlmathrm",Text
"\\mathrm{\\epsilon}"),(Text
"unicode-math",Text
"\\upvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\epsilonup (kpfonts mathdesign), GREEK LUNATE EPSILON SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\1014', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\backepsilon"),(Text
"wrisym",Text
"\\backepsilon"),(Text
"unicode-math",Text
"\\upbackepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"GREEK REVERSED LUNATE EPSILON SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\1064', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"t \\CYRSHHA (T2A), Shcy, CYRILLIC CAPITAL LETTER SHA"}
, Record {uchar :: Char
uchar = Char
'\8192', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"enquad"}
, Record {uchar :: Char
uchar = Char
'\8193', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\quad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"emquad"}
, Record {uchar :: Char
uchar = Char
'\8194', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ensp (half an em)"}
, Record {uchar :: Char
uchar = Char
'\8195', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"emsp"}
, Record {uchar :: Char
uchar = Char
'\8196', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"THREE-PER-EM SPACE"}
, Record {uchar :: Char
uchar = Char
'\8197', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FOUR-PER-EM SPACE, mid space"}
, Record {uchar :: Char
uchar = Char
'\8198', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SIX-PER-EM SPACE"}
, Record {uchar :: Char
uchar = Char
'\8199', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FIGURE SPACE"}
, Record {uchar :: Char
uchar = Char
'\8201', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\,")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"THIN SPACE"}
, Record {uchar :: Char
uchar = Char
'\8202', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HAIR SPACE"}
, Record {uchar :: Char
uchar = Char
'\8203', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\hspace{0pt}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"zwsp"}
, Record {uchar :: Char
uchar = Char
'\8208', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HYPHEN (true graphic)"}
, Record {uchar :: Char
uchar = Char
'\8210', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"dash"}
, Record {uchar :: Char
uchar = Char
'\8211', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ndash"}
, Record {uchar :: Char
uchar = Char
'\8212', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mdash"}
, Record {uchar :: Char
uchar = Char
'\8213', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\horizbar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HORIZONTAL BAR"}
, Record {uchar :: Char
uchar = Char
'\8214', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\|"),(Text
"base",Text
"\\Vert"),(Text
"unicode-math",Text
"\\Vert")], category :: TeXSymbolType
category = TeXSymbolType
Fence, comments :: Text
comments = Text
"double vertical bar"}
, Record {uchar :: Char
uchar = Char
'\8215', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twolowline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE LOW LINE (spacing)"}
, Record {uchar :: Char
uchar = Char
'\8220', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"``")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = Text
"Opening curly quote"}
, Record {uchar :: Char
uchar = Char
'\8221', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\"")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = Text
"Closing curly quote"}
, Record {uchar :: Char
uchar = Char
'\8224', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\dagger"),(Text
"unicode-math",Text
"\\dagger")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DAGGER relation"}
, Record {uchar :: Char
uchar = Char
'\8225', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ddagger"),(Text
"unicode-math",Text
"\\ddagger")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOUBLE DAGGER relation"}
, Record {uchar :: Char
uchar = Char
'\8226', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bullet"),(Text
"unicode-math",Text
"\\smblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"b: round BULLET, filled"}
, Record {uchar :: Char
uchar = Char
'\8229', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\enleadertwodots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"double baseline dot (en leader)"}
, Record {uchar :: Char
uchar = Char
'\8230', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ldots"),(Text
"unicode-math",Text
"\\unicodeellipsis")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ellipsis (horizontal)"}
, Record {uchar :: Char
uchar = Char
'\8242', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\prime"),(Text
"unicode-math",Text
"\\prime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PRIME or minute, not superscripted"}
, Record {uchar :: Char
uchar = Char
'\8243', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\second"),(Text
"unicode-math",Text
"\\dprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE PRIME or second, not superscripted"}
, Record {uchar :: Char
uchar = Char
'\8244', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\third"),(Text
"unicode-math",Text
"\\trprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TRIPLE PRIME (not superscripted)"}
, Record {uchar :: Char
uchar = Char
'\8245', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\backprime"),(Text
"unicode-math",Text
"\\backprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"reverse prime, not superscripted"}
, Record {uchar :: Char
uchar = Char
'\8246', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\backdprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"double reverse prime, not superscripted"}
, Record {uchar :: Char
uchar = Char
'\8247', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\backtrprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"triple reverse prime, not superscripted"}
, Record {uchar :: Char
uchar = Char
'\8248', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\caretinsert")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CARET (insertion mark)"}
, Record {uchar :: Char
uchar = Char
'\8251', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"REFERENCE MARK, Japanese kome jirushi"}
, Record {uchar :: Char
uchar = Char
'\8252', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"!!"),(Text
"unicode-math",Text
"\\Exclam")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE EXCLAMATION MARK"}
, Record {uchar :: Char
uchar = Char
'\8256', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\cat"),(Text
"unicode-math",Text
"\\tieconcat")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CHARACTER TIE, z notation sequence concatenation"}
, Record {uchar :: Char
uchar = Char
'\8259', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hyphenbullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"rectangle, filled (HYPHEN BULLET)"}
, Record {uchar :: Char
uchar = Char
'\8260', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"/"),(Text
"unicode-math",Text
"\\fracslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"FRACTION SLASH"}
, Record {uchar :: Char
uchar = Char
'\8263', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"??"),(Text
"unicode-math",Text
"\\Question")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE QUESTION MARK"}
, Record {uchar :: Char
uchar = Char
'\8270', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"lowast, LOW ASTERISK"}
, Record {uchar :: Char
uchar = Char
'\8271', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"bsemi, REVERSED SEMICOLON"}
, Record {uchar :: Char
uchar = Char
'\8272', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\closure")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CLOSE UP (editing mark)"}
, Record {uchar :: Char
uchar = Char
'\8273', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"Ast"}
, Record {uchar :: Char
uchar = Char
'\8274', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"./.")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"COMMERCIAL MINUS SIGN"}
, Record {uchar :: Char
uchar = Char
'\8279', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\fourth"),(Text
"unicode-math",Text
"\\qprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"QUADRUPLE PRIME, not superscripted"}
, Record {uchar :: Char
uchar = Char
'\8287', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\:"),(Text
"amsmath",Text
"\\medspace")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEDIUM MATHEMATICAL SPACE, four-eighteenths of an em"}
, Record {uchar :: Char
uchar = Char
'\8289', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FUNCTION APPLICATION"}
, Record {uchar :: Char
uchar = Char
'\8290', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INVISIBLE TIMES"}
, Record {uchar :: Char
uchar = Char
'\8291', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INVISIBLE SEPARATOR"}
, Record {uchar :: Char
uchar = Char
'\8292', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INVISIBLE PLUS"}
, Record {uchar :: Char
uchar = Char
'\8314', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUPERSCRIPT PLUS SIGN subscript operators"}
, Record {uchar :: Char
uchar = Char
'\8315', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUPERSCRIPT MINUS subscript operators"}
, Record {uchar :: Char
uchar = Char
'\8316', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUPERSCRIPT EQUALS SIGN subscript operators"}
, Record {uchar :: Char
uchar = Char
'\8317', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"SUPERSCRIPT LEFT PARENTHESIS subscript operators"}
, Record {uchar :: Char
uchar = Char
'\8318', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"SUPERSCRIPT RIGHT PARENTHESIS subscript operators"}
, Record {uchar :: Char
uchar = Char
'\8330', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUBSCRIPT PLUS SIGN superscript operators"}
, Record {uchar :: Char
uchar = Char
'\8331', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUBSCRIPT MINUS superscript operators"}
, Record {uchar :: Char
uchar = Char
'\8332', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUBSCRIPT EQUALS SIGN superscript operators"}
, Record {uchar :: Char
uchar = Char
'\8333', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"SUBSCRIPT LEFT PARENTHESIS superscript operators"}
, Record {uchar :: Char
uchar = Char
'\8334', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"SUBSCRIPT RIGHT PARENTHESIS superscript operators"}
, Record {uchar :: Char
uchar = Char
'\8364', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\euro")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EURO SIGN"}
, Record {uchar :: Char
uchar = Char
'\8400', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\lvec"),(Text
"unicode-math",Text
"\\leftharpoonaccent")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LEFT HARPOON ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8401', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\vec"),(Text
"unicode-math",Text
"\\rightharpoonaccent")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING RIGHT HARPOON ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8402', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vertoverlay")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LONG VERTICAL LINE OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8403', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING SHORT VERTICAL LINE OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8404', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ANTICLOCKWISE ARROW ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8406', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LVec"),(Text
"base",Text
"\\overleftarrow"),(Text
"unicode-math",Text
"\\overleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LEFT ARROW ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8407', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\vec"),(Text
"wrisym",Text
"\\Vec"),(Text
"unicode-math",Text
"\\vec")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"# \\overrightarrow, COMBINING RIGHT ARROW ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8408', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING RING OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8409', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING CLOCKWISE RING OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8410', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ANTICLOCKWISE RING OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8411', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\dddot"),(Text
"wrisym",Text
"\\DDDot"),(Text
"unicode-math",Text
"\\dddot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING THREE DOTS ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8412', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\ddddot"),(Text
"unicode-math",Text
"\\ddddot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING FOUR DOTS ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8413', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\enclosecircle")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ENCLOSING CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\8414', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\enclosesquare")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ENCLOSING SQUARE"}
, Record {uchar :: Char
uchar = Char
'\8415', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\enclosediamond")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ENCLOSING DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\8417', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\overleftrightarrow"),(Text
"unicode-math",Text
"\\overleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LEFT RIGHT ARROW ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8420', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\enclosetriangle")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ENCLOSING UPWARD POINTING TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\8421', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING REVERSE SOLIDUS OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8422', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING DOUBLE VERTICAL STROKE OVERLAY, z notation finite function diacritic"}
, Record {uchar :: Char
uchar = Char
'\8423', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\annuity")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ANNUITY SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\8424', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\threeunderdot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING TRIPLE UNDERDOT"}
, Record {uchar :: Char
uchar = Char
'\8425', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\widebridgeabove")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING WIDE BRIDGE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8426', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LEFTWARDS ARROW OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8427', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LONG DOUBLE SOLIDUS OVERLAY"}
, Record {uchar :: Char
uchar = Char
'\8428', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\underrightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING RIGHTWARDS HARPOON WITH BARB DOWNWARDS"}
, Record {uchar :: Char
uchar = Char
'\8429', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\underleftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LEFTWARDS HARPOON WITH BARB DOWNWARDS"}
, Record {uchar :: Char
uchar = Char
'\8430', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\underleftarrow"),(Text
"unicode-math",Text
"\\underleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING LEFT ARROW BELOW"}
, Record {uchar :: Char
uchar = Char
'\8431', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\underrightarrow"),(Text
"unicode-math",Text
"\\underrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING RIGHT ARROW BELOW"}
, Record {uchar :: Char
uchar = Char
'\8432', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\asteraccent")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"COMBINING ASTERISK ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8450', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{C}"),(Text
"dsfont",Text
"\\mathds{C}"),(Text
"unicode-math",Text
"\\BbbC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"open face C"}
, Record {uchar :: Char
uchar = Char
'\8455', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\Euler"),(Text
"unicode-math",Text
"\\Eulerconst")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EULER CONSTANT"}
, Record {uchar :: Char
uchar = Char
'\8458', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{g}"),(Text
"unicode-math",Text
"\\mscrg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/scr g, script small letter g"}
, Record {uchar :: Char
uchar = Char
'\8459', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{H}"),(Text
"unicode-math",Text
"\\mscrH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"hamiltonian (script capital H)"}
, Record {uchar :: Char
uchar = Char
'\8460', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{H}"),(Text
"unicode-math",Text
"\\mfrakH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/frak H, black-letter capital H"}
, Record {uchar :: Char
uchar = Char
'\8461', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{H}"),(Text
"dsfont",Text
"\\mathds{H}"),(Text
"unicode-math",Text
"\\BbbH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"open face capital H"}
, Record {uchar :: Char
uchar = Char
'\8462', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"h"),(Text
"unicode-math",Text
"\\Planckconst")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"Planck constant"}
, Record {uchar :: Char
uchar = Char
'\8463', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\hslash"),(Text
"fourier",Text
"\\hslash"),(Text
"arevmath",Text
"\\hslash"),(Text
"wrisym",Text
"\\HBar"),(Text
"unicode-math",Text
"\\hslash")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"#\\hbar, Planck's h over 2pi"}
, Record {uchar :: Char
uchar = Char
'\8464', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{I}"),(Text
"unicode-math",Text
"\\mscrI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/scr I, script capital I"}
, Record {uchar :: Char
uchar = Char
'\8465', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Im"),(Text
"eufrak",Text
"\\mathfrak{I}"),(Text
"unicode-math",Text
"\\Im")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"imaginary part"}
, Record {uchar :: Char
uchar = Char
'\8466', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{L}"),(Text
"unicode-math",Text
"\\mscrL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"lagrangian (script capital L)"}
, Record {uchar :: Char
uchar = Char
'\8467', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ell"),(Text
"unicode-math",Text
"\\ell")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"cursive small l"}
, Record {uchar :: Char
uchar = Char
'\8469', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{N}"),(Text
"dsfont",Text
"\\mathds{N}"),(Text
"unicode-math",Text
"\\BbbN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"open face N"}
, Record {uchar :: Char
uchar = Char
'\8472', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\wp"),(Text
"unicode-math",Text
"\\wp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"weierstrass p"}
, Record {uchar :: Char
uchar = Char
'\8473', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{P}"),(Text
"dsfont",Text
"\\mathds{P}"),(Text
"unicode-math",Text
"\\BbbP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"open face P"}
, Record {uchar :: Char
uchar = Char
'\8474', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{Q}"),(Text
"dsfont",Text
"\\mathds{Q}"),(Text
"unicode-math",Text
"\\BbbQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"open face Q"}
, Record {uchar :: Char
uchar = Char
'\8475', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{R}"),(Text
"unicode-math",Text
"\\mscrR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/scr R, script capital R"}
, Record {uchar :: Char
uchar = Char
'\8476', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Re"),(Text
"eufrak",Text
"\\mathfrak{R}"),(Text
"unicode-math",Text
"\\Re")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"real part"}
, Record {uchar :: Char
uchar = Char
'\8477', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{R}"),(Text
"dsfont",Text
"\\mathds{R}"),(Text
"unicode-math",Text
"\\BbbR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"open face R"}
, Record {uchar :: Char
uchar = Char
'\8484', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{Z}"),(Text
"dsfont",Text
"\\mathds{Z}"),(Text
"unicode-math",Text
"\\BbbZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"open face Z"}
, Record {uchar :: Char
uchar = Char
'\8486', commands :: [(Text, Text)]
commands = [(Text
"mathcomp",Text
"\\tcohm"),(Text
"base",Text
"\\mathrm{\\Omega}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"ohm (deprecated in math, use greek letter)"}
, Record {uchar :: Char
uchar = Char
'\8487', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\mho"),(Text
"arevmath",Text
"\\mho"),(Text
"wrisym",Text
"\\Mho"),(Text
"unicode-math",Text
"\\mho")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"t \\agemO (wasysym), conductance"}
, Record {uchar :: Char
uchar = Char
'\8488', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{Z}"),(Text
"unicode-math",Text
"\\mfrakZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/frak Z, black-letter capital Z"}
, Record {uchar :: Char
uchar = Char
'\8489', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\turnediota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"turned iota"}
, Record {uchar :: Char
uchar = Char
'\8491', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\Angstroem"),(Text
"base",Text
"\\mathring{\\mathrm{A}}"),(Text
"unicode-math",Text
"\\Angstrom")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"\197ngstr\246m capital A with ring"}
, Record {uchar :: Char
uchar = Char
'\8492', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{B}"),(Text
"unicode-math",Text
"\\mscrB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"bernoulli function (script capital B)"}
, Record {uchar :: Char
uchar = Char
'\8493', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{C}"),(Text
"unicode-math",Text
"\\mfrakC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"black-letter capital C"}
, Record {uchar :: Char
uchar = Char
'\8495', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{e}"),(Text
"unicode-math",Text
"\\mscre")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/scr e, script small letter e"}
, Record {uchar :: Char
uchar = Char
'\8496', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{E}"),(Text
"unicode-math",Text
"\\mscrE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/scr E, script capital E"}
, Record {uchar :: Char
uchar = Char
'\8497', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{F}"),(Text
"unicode-math",Text
"\\mscrF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"/scr F, script capital F"}
, Record {uchar :: Char
uchar = Char
'\8498', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Finv"),(Text
"unicode-math",Text
"\\Finv")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TURNED CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\8499', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{M}"),(Text
"unicode-math",Text
"\\mscrM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"physics m-matrix (SCRIPT CAPITAL M)"}
, Record {uchar :: Char
uchar = Char
'\8500', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{o}"),(Text
"unicode-math",Text
"\\mscro")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"order of (SCRIPT SMALL O)"}
, Record {uchar :: Char
uchar = Char
'\8501', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\aleph"),(Text
"unicode-math",Text
"\\aleph")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"aleph, hebrew"}
, Record {uchar :: Char
uchar = Char
'\8502', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\beth"),(Text
"wrisym",Text
"\\beth"),(Text
"unicode-math",Text
"\\beth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"beth, hebrew"}
, Record {uchar :: Char
uchar = Char
'\8503', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gimel"),(Text
"wrisym",Text
"\\gimel"),(Text
"unicode-math",Text
"\\gimel")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"gimel, hebrew"}
, Record {uchar :: Char
uchar = Char
'\8504', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\daleth"),(Text
"wrisym",Text
"\\daleth"),(Text
"unicode-math",Text
"\\daleth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"daleth, hebrew"}
, Record {uchar :: Char
uchar = Char
'\8508', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{\\pi}"),(Text
"unicode-math",Text
"\\Bbbpi")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"\\DoublePi (wrisym), DOUBLE-STRUCK SMALL PI"}
, Record {uchar :: Char
uchar = Char
'\8509', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{\\gamma}"),(Text
"unicode-math",Text
"\\Bbbgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"\\EulerGamma (wrisym), DOUBLE-STRUCK SMALL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\8510', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{\\Gamma}"),(Text
"unicode-math",Text
"\\BbbGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"DOUBLE-STRUCK CAPITAL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\8511', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{\\Pi}"),(Text
"unicode-math",Text
"\\BbbPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"DOUBLE-STRUCK CAPITAL PI"}
, Record {uchar :: Char
uchar = Char
'\8512', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{\\Sigma}"),(Text
"unicode-math",Text
"\\Bbbsum")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"DOUBLE-STRUCK N-ARY SUMMATION"}
, Record {uchar :: Char
uchar = Char
'\8513', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Game"),(Text
"unicode-math",Text
"\\Game")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TURNED SANS-SERIF CAPITAL G (amssymb has mirrored G)"}
, Record {uchar :: Char
uchar = Char
'\8514', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sansLturned")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TURNED SANS-SERIF CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\8515', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sansLmirrored")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"REVERSED SANS-SERIF CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\8516', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\Yup"),(Text
"unicode-math",Text
"\\Yup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TURNED SANS-SERIF CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\8517', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\CapitalDifferentialD"),(Text
"wrisym",Text
"\\DD"),(Text
"unicode-math",Text
"\\mitBbbD")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE-STRUCK ITALIC CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\8518', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\DifferentialD"),(Text
"wrisym",Text
"\\dd"),(Text
"unicode-math",Text
"\\mitBbbd")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE-STRUCK ITALIC SMALL D"}
, Record {uchar :: Char
uchar = Char
'\8519', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\ExponetialE"),(Text
"wrisym",Text
"\\ee"),(Text
"unicode-math",Text
"\\mitBbbe")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE-STRUCK ITALIC SMALL E"}
, Record {uchar :: Char
uchar = Char
'\8520', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\ComplexI"),(Text
"wrisym",Text
"\\ii"),(Text
"unicode-math",Text
"\\mitBbbi")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE-STRUCK ITALIC SMALL I"}
, Record {uchar :: Char
uchar = Char
'\8521', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\ComplexJ"),(Text
"wrisym",Text
"\\jj"),(Text
"unicode-math",Text
"\\mitBbbj")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOUBLE-STRUCK ITALIC SMALL J"}
, Record {uchar :: Char
uchar = Char
'\8522', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\PropertyLine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PROPERTY LINE"}
, Record {uchar :: Char
uchar = Char
'\8523', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\invamp"),(Text
"stmaryrd",Text
"\\bindnasrepma"),(Text
"unicode-math",Text
"\\upand")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TURNED AMPERSAND"}
, Record {uchar :: Char
uchar = Char
'\8592', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\leftarrow"),(Text
"base",Text
"\\gets"),(Text
"unicode-math",Text
"\\leftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"a: leftward arrow"}
, Record {uchar :: Char
uchar = Char
'\8593', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\uparrow"),(Text
"unicode-math",Text
"\\uparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"upward arrow"}
, Record {uchar :: Char
uchar = Char
'\8594', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rightarrow"),(Text
"base",Text
"\\to"),(Text
"unicode-math",Text
"\\rightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\tfun (oz), = \\fun (oz), rightward arrow, z notation total function"}
, Record {uchar :: Char
uchar = Char
'\8595', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\downarrow"),(Text
"unicode-math",Text
"\\downarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"downward arrow"}
, Record {uchar :: Char
uchar = Char
'\8596', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\leftrightarrow"),(Text
"oz",Text
"\\rel"),(Text
"unicode-math",Text
"\\leftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT RIGHT ARROW, z notation relation"}
, Record {uchar :: Char
uchar = Char
'\8597', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\updownarrow"),(Text
"unicode-math",Text
"\\updownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"up and down arrow"}
, Record {uchar :: Char
uchar = Char
'\8598', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nwarrow"),(Text
"unicode-math",Text
"\\nwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"nw pointing arrow"}
, Record {uchar :: Char
uchar = Char
'\8599', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\nearrow"),(Text
"unicode-math",Text
"\\nearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ne pointing arrow"}
, Record {uchar :: Char
uchar = Char
'\8600', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\searrow"),(Text
"unicode-math",Text
"\\searrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"se pointing arrow"}
, Record {uchar :: Char
uchar = Char
'\8601', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\swarrow"),(Text
"unicode-math",Text
"\\swarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"sw pointing arrow"}
, Record {uchar :: Char
uchar = Char
'\8602', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nleftarrow"),(Text
"unicode-math",Text
"\\nleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not left arrow"}
, Record {uchar :: Char
uchar = Char
'\8603', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nrightarrow"),(Text
"unicode-math",Text
"\\nrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not right arrow"}
, Record {uchar :: Char
uchar = Char
'\8604', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftwavearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left arrow-wavy"}
, Record {uchar :: Char
uchar = Char
'\8605', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightwavearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right arrow-wavy"}
, Record {uchar :: Char
uchar = Char
'\8606', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\twoheadleftarrow"),(Text
"unicode-math",Text
"\\twoheadleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left two-headed arrow"}
, Record {uchar :: Char
uchar = Char
'\8607', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twoheaduparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"up two-headed arrow"}
, Record {uchar :: Char
uchar = Char
'\8608', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\twoheadrightarrow"),(Text
"oz",Text
"\\tsur"),(Text
"unicode-math",Text
"\\twoheadrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\surj (oz), right two-headed arrow, z notation total surjection"}
, Record {uchar :: Char
uchar = Char
'\8609', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twoheaddownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"down two-headed arrow"}
, Record {uchar :: Char
uchar = Char
'\8610', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leftarrowtail"),(Text
"unicode-math",Text
"\\leftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left arrow-tailed"}
, Record {uchar :: Char
uchar = Char
'\8611', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\rightarrowtail"),(Text
"oz",Text
"\\tinj"),(Text
"unicode-math",Text
"\\rightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\inj (oz), right arrow-tailed, z notation total injection"}
, Record {uchar :: Char
uchar = Char
'\8612', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\mapsfrom"),(Text
"kpfonts",Text
"\\mappedfrom"),(Text
"unicode-math",Text
"\\mapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"maps to, leftward"}
, Record {uchar :: Char
uchar = Char
'\8613', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\MapsUp"),(Text
"unicode-math",Text
"\\mapsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"maps to, upward"}
, Record {uchar :: Char
uchar = Char
'\8614', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mapsto"),(Text
"unicode-math",Text
"\\mapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"maps to, rightward, z notation maplet"}
, Record {uchar :: Char
uchar = Char
'\8615', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\MapsDown"),(Text
"unicode-math",Text
"\\mapsdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"maps to, downward"}
, Record {uchar :: Char
uchar = Char
'\8616', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\updownarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UP DOWN ARROW WITH BASE (perpendicular)"}
, Record {uchar :: Char
uchar = Char
'\8617', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\hookleftarrow"),(Text
"unicode-math",Text
"\\hookleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left arrow-hooked"}
, Record {uchar :: Char
uchar = Char
'\8618', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\hookrightarrow"),(Text
"unicode-math",Text
"\\hookrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right arrow-hooked"}
, Record {uchar :: Char
uchar = Char
'\8619', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\looparrowleft"),(Text
"unicode-math",Text
"\\looparrowleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left arrow-looped"}
, Record {uchar :: Char
uchar = Char
'\8620', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\looparrowright"),(Text
"unicode-math",Text
"\\looparrowright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right arrow-looped"}
, Record {uchar :: Char
uchar = Char
'\8621', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leftrightsquigarrow"),(Text
"unicode-math",Text
"\\leftrightsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left and right arr-wavy"}
, Record {uchar :: Char
uchar = Char
'\8622', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nleftrightarrow"),(Text
"unicode-math",Text
"\\nleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not left and right arrow"}
, Record {uchar :: Char
uchar = Char
'\8623', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\lightning"),(Text
"unicode-math",Text
"\\downzigzagarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"t \\Lightning (marvosym), DOWNWARDS ZIGZAG ARROW"}
, Record {uchar :: Char
uchar = Char
'\8624', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Lsh"),(Text
"unicode-math",Text
"\\Lsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"a: UPWARDS ARROW WITH TIP LEFTWARDS"}
, Record {uchar :: Char
uchar = Char
'\8625', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Rsh"),(Text
"unicode-math",Text
"\\Rsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"a: UPWARDS ARROW WITH TIP RIGHTWARDS"}
, Record {uchar :: Char
uchar = Char
'\8626', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\dlsh"),(Text
"unicode-math",Text
"\\Ldsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left down angled arrow"}
, Record {uchar :: Char
uchar = Char
'\8627', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\drsh"),(Text
"unicode-math",Text
"\\Rdsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right down angled arrow"}
, Record {uchar :: Char
uchar = Char
'\8628', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\linefeed")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH CORNER DOWNWARDS"}
, Record {uchar :: Char
uchar = Char
'\8629', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\carriagereturn")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"downwards arrow with corner leftward = carriage return"}
, Record {uchar :: Char
uchar = Char
'\8630', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\curvearrowleft"),(Text
"fourier",Text
"\\curvearrowleft"),(Text
"unicode-math",Text
"\\curvearrowleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left curved arrow"}
, Record {uchar :: Char
uchar = Char
'\8631', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\curvearrowright"),(Text
"fourier",Text
"\\curvearrowright"),(Text
"unicode-math",Text
"\\curvearrowright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right curved arrow"}
, Record {uchar :: Char
uchar = Char
'\8632', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\barovernorthwestarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH WEST ARROW TO LONG BAR"}
, Record {uchar :: Char
uchar = Char
'\8633', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\barleftarrowrightarrowba")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFTWARDS ARROW TO BAR OVER RIGHTWARDS ARROW TO BAR"}
, Record {uchar :: Char
uchar = Char
'\8634', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\circlearrowleft"),(Text
"wasysym",Text
"\\leftturn"),(Text
"unicode-math",Text
"\\acwopencirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ANTICLOCKWISE OPEN CIRCLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8635', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\circlearrowright"),(Text
"wasysym",Text
"\\rightturn"),(Text
"unicode-math",Text
"\\cwopencirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CLOCKWISE OPEN CIRCLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8636', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\leftharpoonup"),(Text
"unicode-math",Text
"\\leftharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left harpoon-up"}
, Record {uchar :: Char
uchar = Char
'\8637', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\leftharpoondown"),(Text
"unicode-math",Text
"\\leftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left harpoon-down"}
, Record {uchar :: Char
uchar = Char
'\8638', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\upharpoonright"),(Text
"amssymb",Text
"\\restriction"),(Text
"unicode-math",Text
"\\upharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\upharpoonrightup (wrisym), a: up harpoon-right"}
, Record {uchar :: Char
uchar = Char
'\8639', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\upharpoonleft"),(Text
"wrisym",Text
"\\upharpoonleftup"),(Text
"unicode-math",Text
"\\upharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"up harpoon-left"}
, Record {uchar :: Char
uchar = Char
'\8640', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rightharpoonup"),(Text
"unicode-math",Text
"\\rightharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right harpoon-up"}
, Record {uchar :: Char
uchar = Char
'\8641', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rightharpoondown"),(Text
"unicode-math",Text
"\\rightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right harpoon-down"}
, Record {uchar :: Char
uchar = Char
'\8642', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\downharpoonright"),(Text
"wrisym",Text
"\\upharpoonrightdown"),(Text
"unicode-math",Text
"\\downharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"down harpoon-right"}
, Record {uchar :: Char
uchar = Char
'\8643', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\downharpoonleft"),(Text
"wrisym",Text
"\\upharpoonleftdown"),(Text
"unicode-math",Text
"\\downharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"down harpoon-left"}
, Record {uchar :: Char
uchar = Char
'\8644', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\rightleftarrows"),(Text
"wrisym",Text
"\\rightleftarrow"),(Text
"unicode-math",Text
"\\rightleftarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right arrow over left arrow"}
, Record {uchar :: Char
uchar = Char
'\8645', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\updownarrows"),(Text
"wrisym",Text
"\\uparrowdownarrow"),(Text
"unicode-math",Text
"\\updownarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"up arrow, down arrow"}
, Record {uchar :: Char
uchar = Char
'\8646', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leftrightarrows"),(Text
"wrisym",Text
"\\leftrightarrow"),(Text
"unicode-math",Text
"\\leftrightarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left arrow over right arrow"}
, Record {uchar :: Char
uchar = Char
'\8647', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leftleftarrows"),(Text
"fourier",Text
"\\leftleftarrows"),(Text
"unicode-math",Text
"\\leftleftarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"two left arrows"}
, Record {uchar :: Char
uchar = Char
'\8648', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\upuparrows"),(Text
"unicode-math",Text
"\\upuparrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"two up arrows"}
, Record {uchar :: Char
uchar = Char
'\8649', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\rightrightarrows"),(Text
"fourier",Text
"\\rightrightarrows"),(Text
"unicode-math",Text
"\\rightrightarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"two right arrows"}
, Record {uchar :: Char
uchar = Char
'\8650', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\downdownarrows"),(Text
"unicode-math",Text
"\\downdownarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"two down arrows"}
, Record {uchar :: Char
uchar = Char
'\8651', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leftrightharpoons"),(Text
"wrisym",Text
"\\revequilibrium"),(Text
"unicode-math",Text
"\\leftrightharpoons")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left harpoon over right"}
, Record {uchar :: Char
uchar = Char
'\8652', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rightleftharpoons"),(Text
"wrisym",Text
"\\equilibrium"),(Text
"unicode-math",Text
"\\rightleftharpoons")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right harpoon over left"}
, Record {uchar :: Char
uchar = Char
'\8653', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nLeftarrow"),(Text
"unicode-math",Text
"\\nLeftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not implied by"}
, Record {uchar :: Char
uchar = Char
'\8654', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nLeftrightarrow"),(Text
"unicode-math",Text
"\\nLeftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not left and right double arrows"}
, Record {uchar :: Char
uchar = Char
'\8655', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nRightarrow"),(Text
"unicode-math",Text
"\\nRightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not implies"}
, Record {uchar :: Char
uchar = Char
'\8656', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Leftarrow"),(Text
"unicode-math",Text
"\\Leftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left double arrow"}
, Record {uchar :: Char
uchar = Char
'\8657', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Uparrow"),(Text
"unicode-math",Text
"\\Uparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"up double arrow"}
, Record {uchar :: Char
uchar = Char
'\8658', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Rightarrow"),(Text
"unicode-math",Text
"\\Rightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right double arrow"}
, Record {uchar :: Char
uchar = Char
'\8659', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Downarrow"),(Text
"unicode-math",Text
"\\Downarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"down double arrow"}
, Record {uchar :: Char
uchar = Char
'\8660', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Leftrightarrow"),(Text
"unicode-math",Text
"\\Leftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left and right double arrow"}
, Record {uchar :: Char
uchar = Char
'\8661', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Updownarrow"),(Text
"unicode-math",Text
"\\Updownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"up and down double arrow"}
, Record {uchar :: Char
uchar = Char
'\8662', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Nwarrow"),(Text
"unicode-math",Text
"\\Nwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"nw pointing double arrow"}
, Record {uchar :: Char
uchar = Char
'\8663', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Nearrow"),(Text
"unicode-math",Text
"\\Nearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ne pointing double arrow"}
, Record {uchar :: Char
uchar = Char
'\8664', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Searrow"),(Text
"unicode-math",Text
"\\Searrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"se pointing double arrow"}
, Record {uchar :: Char
uchar = Char
'\8665', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Swarrow"),(Text
"unicode-math",Text
"\\Swarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"sw pointing double arrow"}
, Record {uchar :: Char
uchar = Char
'\8666', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Lleftarrow"),(Text
"unicode-math",Text
"\\Lleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left triple arrow"}
, Record {uchar :: Char
uchar = Char
'\8667', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Rrightarrow"),(Text
"unicode-math",Text
"\\Rrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right triple arrow"}
, Record {uchar :: Char
uchar = Char
'\8668', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\leftsquigarrow"),(Text
"txfonts",Text
"\\leftsquigarrow"),(Text
"unicode-math",Text
"\\leftsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS SQUIGGLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8669', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\rightsquigarrow"),(Text
"unicode-math",Text
"\\rightsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS SQUIGGLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8670', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nHuparrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS ARROW WITH DOUBLE STROKE"}
, Record {uchar :: Char
uchar = Char
'\8671', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nHdownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWNWARDS ARROW WITH DOUBLE STROKE"}
, Record {uchar :: Char
uchar = Char
'\8672', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\dashleftarrow"),(Text
"unicode-math",Text
"\\leftdasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFTWARDS DASHED ARROW"}
, Record {uchar :: Char
uchar = Char
'\8673', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\updasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS DASHED ARROW"}
, Record {uchar :: Char
uchar = Char
'\8674', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\dashrightarrow"),(Text
"amsfonts",Text
"\\dasharrow"),(Text
"unicode-math",Text
"\\rightdasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHTWARDS DASHED ARROW"}
, Record {uchar :: Char
uchar = Char
'\8675', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\downdasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWNWARDS DASHED ARROW"}
, Record {uchar :: Char
uchar = Char
'\8676', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftArrowBar"),(Text
"unicode-math",Text
"\\barleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW TO BAR"}
, Record {uchar :: Char
uchar = Char
'\8677', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightArrowBar"),(Text
"unicode-math",Text
"\\rightarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW TO BAR"}
, Record {uchar :: Char
uchar = Char
'\8678', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFTWARDS WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8679', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8680', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHTWARDS WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8681', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\downwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWNWARDS WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8682', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\whitearrowupfrombar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS WHITE ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\8683', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS WHITE ARROW ON PEDESTAL"}
, Record {uchar :: Char
uchar = Char
'\8684', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS WHITE ARROW ON PEDESTAL WITH HORIZONTAL BAR"}
, Record {uchar :: Char
uchar = Char
'\8685', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS WHITE ARROW ON PEDESTAL WITH VERTICAL BAR"}
, Record {uchar :: Char
uchar = Char
'\8686', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS WHITE DOUBLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8687', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS WHITE DOUBLE ARROW ON PEDESTAL"}
, Record {uchar :: Char
uchar = Char
'\8688', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHTWARDS WHITE ARROW FROM WALL"}
, Record {uchar :: Char
uchar = Char
'\8689', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH WEST ARROW TO CORNER"}
, Record {uchar :: Char
uchar = Char
'\8690', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SOUTH EAST ARROW TO CORNER"}
, Record {uchar :: Char
uchar = Char
'\8691', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UP DOWN WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\8692', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circleonrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHT ARROW WITH SMALL CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\8693', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\downuparrows"),(Text
"wrisym",Text
"\\downarrowuparrow"),(Text
"unicode-math",Text
"\\downuparrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS ARROW LEFTWARDS OF UPWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\8694', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightthreearrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"THREE RIGHTWARDS ARROWS"}
, Record {uchar :: Char
uchar = Char
'\8695', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8696', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\pfun"),(Text
"unicode-math",Text
"\\nvrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH VERTICAL STROKE, z notation partial function"}
, Record {uchar :: Char
uchar = Char
'\8697', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT RIGHT ARROW WITH VERTICAL STROKE, z notation partial relation"}
, Record {uchar :: Char
uchar = Char
'\8698', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nVleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH DOUBLE VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8699', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\ffun"),(Text
"unicode-math",Text
"\\nVrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH DOUBLE VERTICAL STROKE, z notation finite function"}
, Record {uchar :: Char
uchar = Char
'\8700', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nVleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT RIGHT ARROW WITH DOUBLE VERTICAL STROKE, z notation finite relation"}
, Record {uchar :: Char
uchar = Char
'\8701', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\leftarrowtriangle"),(Text
"unicode-math",Text
"\\leftarrowtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS OPEN-HEADED ARROW"}
, Record {uchar :: Char
uchar = Char
'\8702', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\rightarrowtriangle"),(Text
"unicode-math",Text
"\\rightarrowtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS OPEN-HEADED ARROW"}
, Record {uchar :: Char
uchar = Char
'\8703', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\leftrightarrowtriangle"),(Text
"unicode-math",Text
"\\leftrightarrowtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT RIGHT OPEN-HEADED ARROW"}
, Record {uchar :: Char
uchar = Char
'\8704', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\forall"),(Text
"unicode-math",Text
"\\forall")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FOR ALL"}
, Record {uchar :: Char
uchar = Char
'\8705', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\complement"),(Text
"fourier",Text
"\\complement"),(Text
"unicode-math",Text
"\\complement")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"COMPLEMENT sign"}
, Record {uchar :: Char
uchar = Char
'\8706', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\partial"),(Text
"kpfonts",Text
"\\partialup"),(Text
"unicode-math",Text
"\\partial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PARTIAL DIFFERENTIAL"}
, Record {uchar :: Char
uchar = Char
'\8707', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\exists"),(Text
"oz",Text
"\\exi"),(Text
"unicode-math",Text
"\\exists")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"at least one exists"}
, Record {uchar :: Char
uchar = Char
'\8708', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nexists"),(Text
"fourier",Text
"\\nexists"),(Text
"oz",Text
"\\nexi"),(Text
"unicode-math",Text
"\\nexists")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"negated exists"}
, Record {uchar :: Char
uchar = Char
'\8709', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\varnothing"),(Text
"unicode-math",Text
"\\varnothing")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"circle, slash"}
, Record {uchar :: Char
uchar = Char
'\8710', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathrm{\\Delta}"),(Text
"unicode-math",Text
"\\increment")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"laplacian (Delta; nabla square)"}
, Record {uchar :: Char
uchar = Char
'\8711', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\nabla"),(Text
"unicode-math",Text
"\\nabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NABLA, del, hamilton operator"}
, Record {uchar :: Char
uchar = Char
'\8712', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\in"),(Text
"unicode-math",Text
"\\in")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"set membership, variant"}
, Record {uchar :: Char
uchar = Char
'\8713', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\notin"),(Text
"wrisym",Text
"\\nin"),(Text
"unicode-math",Text
"\\notin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"negated set membership"}
, Record {uchar :: Char
uchar = Char
'\8714', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\in"),(Text
"unicode-math",Text
"\\smallin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"set membership (small set membership)"}
, Record {uchar :: Char
uchar = Char
'\8715', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ni"),(Text
"base",Text
"\\owns"),(Text
"unicode-math",Text
"\\ni")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"contains, variant"}
, Record {uchar :: Char
uchar = Char
'\8716', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\nni"),(Text
"txfonts",Text
"\\notni"),(Text
"unicode-math",Text
"\\nni")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\notowner (mathabx), = \\notowns (fourier), negated contains, variant"}
, Record {uchar :: Char
uchar = Char
'\8717', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ni"), (Text
"unicode-math",Text
"\\smallni")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"r: contains (SMALL CONTAINS AS MEMBER)"}
, Record {uchar :: Char
uchar = Char
'\8718', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\blacksquare"),(Text
"unicode-math",Text
"\\QED")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"END OF PROOF"}
, Record {uchar :: Char
uchar = Char
'\8719', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\prod"),(Text
"unicode-math",Text
"\\prod")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"product operator"}
, Record {uchar :: Char
uchar = Char
'\8720', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\coprod"),(Text
"unicode-math",Text
"\\coprod")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"coproduct operator"}
, Record {uchar :: Char
uchar = Char
'\8721', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sum"),(Text
"unicode-math",Text
"\\sum")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"summation operator"}
, Record {uchar :: Char
uchar = Char
'\8722', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"-"),(Text
"unicode-math",Text
"\\minus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINUS SIGN"}
, Record {uchar :: Char
uchar = Char
'\8723', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mp"),(Text
"unicode-math",Text
"\\mp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINUS-OR-PLUS SIGN"}
, Record {uchar :: Char
uchar = Char
'\8724', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\dotplus"),(Text
"unicode-math",Text
"\\dotplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"plus sign, dot above"}
, Record {uchar :: Char
uchar = Char
'\8725', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\slash"),(Text
"unicode-math",Text
"\\divslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DIVISION SLASH"}
, Record {uchar :: Char
uchar = Char
'\8726', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\smallsetminus"),(Text
"fourier",Text
"\\smallsetminus"),(Text
"unicode-math",Text
"\\smallsetminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"small SET MINUS (cf. reverse solidus)"}
, Record {uchar :: Char
uchar = Char
'\8727', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ast"),(Text
"unicode-math",Text
"\\ast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"ASTERISK OPERATOR (Hodge star operator)"}
, Record {uchar :: Char
uchar = Char
'\8728', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\circ"),(Text
"unicode-math",Text
"\\vysmwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"composite function (small circle)"}
, Record {uchar :: Char
uchar = Char
'\8729', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bullet"),(Text
"unicode-math",Text
"\\vysmblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"BULLET OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\8730', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sqrt"),(Text
"unicode-math",Text
"\\sqrt")], category :: TeXSymbolType
category = TeXSymbolType
Rad, comments :: Text
comments = Text
"radical"}
, Record {uchar :: Char
uchar = Char
'\8731', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sqrt[3]"),(Text
"unicode-math",Text
"\\cuberoot")], category :: TeXSymbolType
category = TeXSymbolType
Rad, comments :: Text
comments = Text
"CUBE ROOT"}
, Record {uchar :: Char
uchar = Char
'\8732', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sqrt[4]"),(Text
"unicode-math",Text
"\\fourthroot")], category :: TeXSymbolType
category = TeXSymbolType
Rad, comments :: Text
comments = Text
"FOURTH ROOT"}
, Record {uchar :: Char
uchar = Char
'\8733', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\propto"),(Text
"amssymb",Text
"\\varpropto"),(Text
"unicode-math",Text
"\\propto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"is PROPORTIONAL TO"}
, Record {uchar :: Char
uchar = Char
'\8734', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\infty"),(Text
"unicode-math",Text
"\\infty")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INFINITY"}
, Record {uchar :: Char
uchar = Char
'\8735', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\rightangle"),(Text
"unicode-math",Text
"\\rightangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"right (90 degree) angle"}
, Record {uchar :: Char
uchar = Char
'\8736', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\angle"),(Text
"unicode-math",Text
"\\angle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ANGLE"}
, Record {uchar :: Char
uchar = Char
'\8737', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\measuredangle"),(Text
"wrisym",Text
"\\measuredangle"),(Text
"unicode-math",Text
"\\measuredangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE"}
, Record {uchar :: Char
uchar = Char
'\8738', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\sphericalangle"),(Text
"wrisym",Text
"\\sphericalangle"),(Text
"unicode-math",Text
"\\sphericalangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SPHERICAL ANGLE"}
, Record {uchar :: Char
uchar = Char
'\8739', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mid"),(Text
"unicode-math",Text
"\\mid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"r: DIVIDES"}
, Record {uchar :: Char
uchar = Char
'\8740', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nmid"),(Text
"unicode-math",Text
"\\nmid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"negated mid, DOES NOT DIVIDE"}
, Record {uchar :: Char
uchar = Char
'\8741', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\parallel"),(Text
"unicode-math",Text
"\\parallel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"parallel"}
, Record {uchar :: Char
uchar = Char
'\8742', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nparallel"),(Text
"fourier",Text
"\\nparallel"),(Text
"unicode-math",Text
"\\nparallel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not parallel"}
, Record {uchar :: Char
uchar = Char
'\8743', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\wedge"),(Text
"base",Text
"\\land"),(Text
"unicode-math",Text
"\\wedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"b: LOGICAL AND"}
, Record {uchar :: Char
uchar = Char
'\8744', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\vee"),(Text
"base",Text
"\\lor"),(Text
"unicode-math",Text
"\\vee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"b: LOGICAL OR"}
, Record {uchar :: Char
uchar = Char
'\8745', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\cap"),(Text
"unicode-math",Text
"\\cap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\8746', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\cup"),(Text
"unicode-math",Text
"\\cup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"UNION or logical sum"}
, Record {uchar :: Char
uchar = Char
'\8747', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\int"),(Text
"unicode-math",Text
"\\int")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL operator"}
, Record {uchar :: Char
uchar = Char
'\8748', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\iint"),(Text
"fourier",Text
"\\iint"),(Text
"esint",Text
"\\iint"),(Text
"wasysym",Text
"\\iint"),(Text
"unicode-math",Text
"\\iint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"DOUBLE INTEGRAL operator"}
, Record {uchar :: Char
uchar = Char
'\8749', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\iiint"),(Text
"fourier",Text
"\\iiint"),(Text
"esint",Text
"\\iiint"),(Text
"wasysym",Text
"\\iiint"),(Text
"unicode-math",Text
"\\iiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"TRIPLE INTEGRAL operator"}
, Record {uchar :: Char
uchar = Char
'\8750', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\oint"),(Text
"unicode-math",Text
"\\oint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"CONTOUR INTEGRAL operator"}
, Record {uchar :: Char
uchar = Char
'\8751', commands :: [(Text, Text)]
commands = [(Text
"esint",Text
"\\oiint"),(Text
"wasysym",Text
"\\oiint"),(Text
"fourier",Text
"\\oiint"),(Text
"wrisym",Text
"\\dbloint"),(Text
"unicode-math",Text
"\\oiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"double contour integral operator"}
, Record {uchar :: Char
uchar = Char
'\8752', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\oiiint"),(Text
"fourier",Text
"\\oiiint"),(Text
"unicode-math",Text
"\\oiiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"triple contour integral operator"}
, Record {uchar :: Char
uchar = Char
'\8753', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intclockwise")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"CLOCKWISE INTEGRAL"}
, Record {uchar :: Char
uchar = Char
'\8754', commands :: [(Text, Text)]
commands = [(Text
"esint",Text
"\\varointclockwise"),(Text
"wrisym",Text
"\\clockoint"),(Text
"unicode-math",Text
"\\varointclockwise")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"contour integral, clockwise"}
, Record {uchar :: Char
uchar = Char
'\8755', commands :: [(Text, Text)]
commands = [(Text
"esint",Text
"\\ointctrclockwise"),(Text
"wrisym",Text
"\\cntclockoint"),(Text
"unicode-math",Text
"\\ointctrclockwise")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"contour integral, anticlockwise"}
, Record {uchar :: Char
uchar = Char
'\8756', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\therefore"),(Text
"wrisym",Text
"\\therefore"),(Text
"wasysym",Text
"\\wasytherefore"),(Text
"unicode-math",Text
"\\therefore")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"THEREFORE"}
, Record {uchar :: Char
uchar = Char
'\8757', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\because"),(Text
"wrisym",Text
"\\because"),(Text
"unicode-math",Text
"\\because")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BECAUSE"}
, Record {uchar :: Char
uchar = Char
'\8758', commands :: [(Text, Text)]
commands = [(Text
"base",Text
":"),(Text
"unicode-math",Text
"\\mathratio")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"x \\colon, RATIO"}
, Record {uchar :: Char
uchar = Char
'\8759', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\Proportion"),(Text
"base",Text
"::"),(Text
"unicode-math",Text
"\\Colon")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"two colons"}
, Record {uchar :: Char
uchar = Char
'\8760', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dotminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"minus sign, dot above"}
, Record {uchar :: Char
uchar = Char
'\8761', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\eqcolon"),(Text
"base",Text
"-:"),(Text
"unicode-math",Text
"\\dashcolon")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EXCESS"}
, Record {uchar :: Char
uchar = Char
'\8762', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dotsminusdots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"minus with four dots, GEOMETRIC PROPORTION"}
, Record {uchar :: Char
uchar = Char
'\8763', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\kernelcontraction")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"HOMOTHETIC"}
, Record {uchar :: Char
uchar = Char
'\8764', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sim"),(Text
"unicode-math",Text
"\\sim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"similar to, TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\8765', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\backsim"),(Text
"unicode-math",Text
"\\backsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"reverse similar"}
, Record {uchar :: Char
uchar = Char
'\8766', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\invlazys")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"most positive, INVERTED LAZY S"}
, Record {uchar :: Char
uchar = Char
'\8767', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\AC"),(Text
"unicode-math",Text
"\\sinewave")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SINE WAVE, alternating current"}
, Record {uchar :: Char
uchar = Char
'\8768', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\wr"),(Text
"unicode-math",Text
"\\wr")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WREATH PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\8769', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nsim"),(Text
"wrisym",Text
"\\nsim"),(Text
"unicode-math",Text
"\\nsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not similar"}
, Record {uchar :: Char
uchar = Char
'\8770', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\eqsim"),(Text
"unicode-math",Text
"\\eqsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equals, similar"}
, Record {uchar :: Char
uchar = Char
'\8771', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\simeq"),(Text
"unicode-math",Text
"\\simeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"similar, equals"}
, Record {uchar :: Char
uchar = Char
'\8772', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\nsimeq"),(Text
"unicode-math",Text
"\\nsime")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not similar, equals"}
, Record {uchar :: Char
uchar = Char
'\8773', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\cong"),(Text
"unicode-math",Text
"\\cong")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"congruent with"}
, Record {uchar :: Char
uchar = Char
'\8774', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"similar, not equals [vert only for 9573 entity]"}
, Record {uchar :: Char
uchar = Char
'\8775', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ncong"),(Text
"wrisym",Text
"\\ncong"),(Text
"unicode-math",Text
"\\ncong")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not congruent with"}
, Record {uchar :: Char
uchar = Char
'\8776', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\approx"),(Text
"unicode-math",Text
"\\approx")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"approximate"}
, Record {uchar :: Char
uchar = Char
'\8777', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\napprox"),(Text
"unicode-math",Text
"\\napprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not approximate"}
, Record {uchar :: Char
uchar = Char
'\8778', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\approxeq"),(Text
"unicode-math",Text
"\\approxeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"approximate, equals"}
, Record {uchar :: Char
uchar = Char
'\8779', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\approxident")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"approximately identical to"}
, Record {uchar :: Char
uchar = Char
'\8780', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\backcong")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ALL EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\8781', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\asymp"),(Text
"unicode-math",Text
"\\asymp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"asymptotically equal to"}
, Record {uchar :: Char
uchar = Char
'\8782', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Bumpeq"),(Text
"wrisym",Text
"\\Bumpeq"),(Text
"unicode-math",Text
"\\Bumpeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"bumpy equals"}
, Record {uchar :: Char
uchar = Char
'\8783', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\bumpeq"),(Text
"wrisym",Text
"\\bumpeq"),(Text
"unicode-math",Text
"\\bumpeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"bumpy equals, equals"}
, Record {uchar :: Char
uchar = Char
'\8784', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\doteq"),(Text
"wrisym",Text
"\\dotequal"),(Text
"unicode-math",Text
"\\doteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equals, single dot above"}
, Record {uchar :: Char
uchar = Char
'\8785', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Doteq"),(Text
"amssymb",Text
"\\doteqdot"),(Text
"unicode-math",Text
"\\Doteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"/doteq r: equals, even dots"}
, Record {uchar :: Char
uchar = Char
'\8786', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\fallingdotseq"),(Text
"unicode-math",Text
"\\fallingdotseq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equals, falling dots"}
, Record {uchar :: Char
uchar = Char
'\8787', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\risingdotseq"),(Text
"unicode-math",Text
"\\risingdotseq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equals, rising dots"}
, Record {uchar :: Char
uchar = Char
'\8788', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\coloneq"),(Text
"txfonts",Text
"\\coloneqq"),(Text
"unicode-math",Text
"\\coloneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\SetDelayed (wrisym), # := colon, equals"}
, Record {uchar :: Char
uchar = Char
'\8789', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\eqcolon"),(Text
"txfonts",Text
"\\eqqcolon"),(Text
"unicode-math",Text
"\\eqcolon")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"# =:, equals, colon"}
, Record {uchar :: Char
uchar = Char
'\8790', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\eqcirc"),(Text
"unicode-math",Text
"\\eqcirc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"circle on equals sign"}
, Record {uchar :: Char
uchar = Char
'\8791', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\circeq"),(Text
"unicode-math",Text
"\\circeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"circle, equals"}
, Record {uchar :: Char
uchar = Char
'\8792', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\arceq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"arc, equals; CORRESPONDS TO"}
, Record {uchar :: Char
uchar = Char
'\8793', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\corresponds"),(Text
"oz",Text
"\\sdef"),(Text
"unicode-math",Text
"\\wedgeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"t \\Corresponds (marvosym), corresponds to (wedge over equals)"}
, Record {uchar :: Char
uchar = Char
'\8794', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\veeeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"logical or, equals"}
, Record {uchar :: Char
uchar = Char
'\8795', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\stareq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"STAR EQUALS"}
, Record {uchar :: Char
uchar = Char
'\8796', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\triangleq"),(Text
"oz",Text
"\\varsdef"),(Text
"unicode-math",Text
"\\triangleq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"triangle, equals"}
, Record {uchar :: Char
uchar = Char
'\8797', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqdef")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equals by definition"}
, Record {uchar :: Char
uchar = Char
'\8798', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"MEASURED BY (m over equals)"}
, Record {uchar :: Char
uchar = Char
'\8799', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\questeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equal with questionmark"}
, Record {uchar :: Char
uchar = Char
'\8800', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\neq"),(Text
"base",Text
"\\ne"),(Text
"unicode-math",Text
"\\ne")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"r: not equal"}
, Record {uchar :: Char
uchar = Char
'\8801', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\equiv"),(Text
"unicode-math",Text
"\\equiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"identical with"}
, Record {uchar :: Char
uchar = Char
'\8802', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\nequiv"),(Text
"unicode-math",Text
"\\nequiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not identical with"}
, Record {uchar :: Char
uchar = Char
'\8803', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Equiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"strict equivalence (4 lines)"}
, Record {uchar :: Char
uchar = Char
'\8804', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\leq"),(Text
"base",Text
"\\le"),(Text
"unicode-math",Text
"\\leq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"r: less-than-or-equal"}
, Record {uchar :: Char
uchar = Char
'\8805', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\geq"),(Text
"base",Text
"\\ge"),(Text
"unicode-math",Text
"\\geq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"r: greater-than-or-equal"}
, Record {uchar :: Char
uchar = Char
'\8806', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leqq"),(Text
"unicode-math",Text
"\\leqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"less, double equals"}
, Record {uchar :: Char
uchar = Char
'\8807', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\geqq"),(Text
"unicode-math",Text
"\\geqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"greater, double equals"}
, Record {uchar :: Char
uchar = Char
'\8808', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lneqq"),(Text
"unicode-math",Text
"\\lneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"less, not double equals"}
, Record {uchar :: Char
uchar = Char
'\8809', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gneqq"),(Text
"unicode-math",Text
"\\gneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"greater, not double equals"}
, Record {uchar :: Char
uchar = Char
'\8810', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ll"),(Text
"unicode-math",Text
"\\ll")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"much less than, type 2"}
, Record {uchar :: Char
uchar = Char
'\8811', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\gg"),(Text
"unicode-math",Text
"\\gg")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"much greater than, type 2"}
, Record {uchar :: Char
uchar = Char
'\8812', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\between"),(Text
"unicode-math",Text
"\\between")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"BETWEEN"}
, Record {uchar :: Char
uchar = Char
'\8813', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\notasymp"),(Text
"wrisym",Text
"\\nasymp"),(Text
"unicode-math",Text
"\\nasymp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not asymptotically equal to"}
, Record {uchar :: Char
uchar = Char
'\8814', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nless"),(Text
"unicode-math",Text
"\\nless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NOT LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\8815', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ngtr"),(Text
"unicode-math",Text
"\\ngtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NOT GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\8816', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nleq"),(Text
"wrisym",Text
"\\nleq"),(Text
"fourier",Text
"\\nleqslant"),(Text
"unicode-math",Text
"\\nleq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not less-than-or-equal"}
, Record {uchar :: Char
uchar = Char
'\8817', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ngeq"),(Text
"wrisym",Text
"\\ngeq"),(Text
"fourier",Text
"\\ngeqslant"),(Text
"unicode-math",Text
"\\ngeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not greater-than-or-equal"}
, Record {uchar :: Char
uchar = Char
'\8818', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lesssim"),(Text
"wasysym",Text
"\\apprle"),(Text
"unicode-math",Text
"\\lesssim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\LessTilde (wrisym), less, similar"}
, Record {uchar :: Char
uchar = Char
'\8819', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gtrsim"),(Text
"wasysym",Text
"\\apprge"),(Text
"unicode-math",Text
"\\gtrsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"= \\GreaterTilde (wrisym), greater, similar"}
, Record {uchar :: Char
uchar = Char
'\8820', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\NotLessTilde"),(Text
"unicode-math",Text
"\\nlesssim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not less, similar"}
, Record {uchar :: Char
uchar = Char
'\8821', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\NotGreaterTilde"),(Text
"unicode-math",Text
"\\ngtrsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not greater, similar"}
, Record {uchar :: Char
uchar = Char
'\8822', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lessgtr"),(Text
"unicode-math",Text
"\\lessgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"less, greater"}
, Record {uchar :: Char
uchar = Char
'\8823', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gtrless"),(Text
"wrisym",Text
"\\GreaterLess"),(Text
"unicode-math",Text
"\\gtrless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"greater, less"}
, Record {uchar :: Char
uchar = Char
'\8824', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nlessgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not less, greater"}
, Record {uchar :: Char
uchar = Char
'\8825', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\NotGreaterLess"),(Text
"unicode-math",Text
"\\ngtrless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not greater, less"}
, Record {uchar :: Char
uchar = Char
'\8826', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\prec"),(Text
"unicode-math",Text
"\\prec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PRECEDES"}
, Record {uchar :: Char
uchar = Char
'\8827', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\succ"),(Text
"unicode-math",Text
"\\succ")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS"}
, Record {uchar :: Char
uchar = Char
'\8828', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\preccurlyeq"),(Text
"wrisym",Text
"\\PrecedesSlantEqual"),(Text
"unicode-math",Text
"\\preccurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"precedes, curly equals"}
, Record {uchar :: Char
uchar = Char
'\8829', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\succcurlyeq"),(Text
"wrisym",Text
"\\SucceedsSlantEqual"),(Text
"unicode-math",Text
"\\succcurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"succeeds, curly equals"}
, Record {uchar :: Char
uchar = Char
'\8830', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\precsim"),(Text
"wrisym",Text
"\\PrecedesTilde"),(Text
"unicode-math",Text
"\\precsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"precedes, similar"}
, Record {uchar :: Char
uchar = Char
'\8831', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\succsim"),(Text
"wrisym",Text
"\\SucceedsTilde"),(Text
"unicode-math",Text
"\\succsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"succeeds, similar"}
, Record {uchar :: Char
uchar = Char
'\8832', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nprec"),(Text
"wrisym",Text
"\\nprec"),(Text
"unicode-math",Text
"\\nprec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not precedes"}
, Record {uchar :: Char
uchar = Char
'\8833', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nsucc"),(Text
"wrisym",Text
"\\nsucc"),(Text
"unicode-math",Text
"\\nsucc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not succeeds"}
, Record {uchar :: Char
uchar = Char
'\8834', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\subset"),(Text
"unicode-math",Text
"\\subset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"subset or is implied by"}
, Record {uchar :: Char
uchar = Char
'\8835', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\supset"),(Text
"unicode-math",Text
"\\supset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"superset or implies"}
, Record {uchar :: Char
uchar = Char
'\8836', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\nsubset"),(Text
"unicode-math",Text
"\\nsubset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not subset, variant [slash negation]"}
, Record {uchar :: Char
uchar = Char
'\8837', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\nsupset"),(Text
"unicode-math",Text
"\\nsupset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not superset, variant [slash negation]"}
, Record {uchar :: Char
uchar = Char
'\8838', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\subseteq"),(Text
"unicode-math",Text
"\\subseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"subset, equals"}
, Record {uchar :: Char
uchar = Char
'\8839', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\supseteq"),(Text
"unicode-math",Text
"\\supseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"superset, equals"}
, Record {uchar :: Char
uchar = Char
'\8840', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nsubseteq"),(Text
"wrisym",Text
"\\nsubseteq"),(Text
"unicode-math",Text
"\\nsubseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not subset, equals"}
, Record {uchar :: Char
uchar = Char
'\8841', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nsupseteq"),(Text
"wrisym",Text
"\\nsupseteq"),(Text
"unicode-math",Text
"\\nsupseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not superset, equals"}
, Record {uchar :: Char
uchar = Char
'\8842', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\subsetneq"),(Text
"fourier",Text
"\\varsubsetneq"),(Text
"unicode-math",Text
"\\subsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"subset, not equals"}
, Record {uchar :: Char
uchar = Char
'\8843', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\supsetneq"),(Text
"unicode-math",Text
"\\supsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"superset, not equals"}
, Record {uchar :: Char
uchar = Char
'\8844', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cupleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTISET"}
, Record {uchar :: Char
uchar = Char
'\8845', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cupdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"union, with dot"}
, Record {uchar :: Char
uchar = Char
'\8846', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\uplus"),(Text
"oz",Text
"\\buni"),(Text
"unicode-math",Text
"\\uplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"plus sign in union"}
, Record {uchar :: Char
uchar = Char
'\8847', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\sqsubset"),(Text
"unicode-math",Text
"\\sqsubset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"square subset"}
, Record {uchar :: Char
uchar = Char
'\8848', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\sqsupset"),(Text
"unicode-math",Text
"\\sqsupset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"square superset"}
, Record {uchar :: Char
uchar = Char
'\8849', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sqsubseteq"),(Text
"unicode-math",Text
"\\sqsubseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"square subset, equals"}
, Record {uchar :: Char
uchar = Char
'\8850', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sqsupseteq"),(Text
"unicode-math",Text
"\\sqsupseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"square superset, equals"}
, Record {uchar :: Char
uchar = Char
'\8851', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sqcap"),(Text
"unicode-math",Text
"\\sqcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"square intersection"}
, Record {uchar :: Char
uchar = Char
'\8852', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sqcup"),(Text
"unicode-math",Text
"\\sqcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"square union"}
, Record {uchar :: Char
uchar = Char
'\8853', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\oplus"),(Text
"unicode-math",Text
"\\oplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"plus sign in circle"}
, Record {uchar :: Char
uchar = Char
'\8854', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ominus"),(Text
"unicode-math",Text
"\\ominus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"minus sign in circle"}
, Record {uchar :: Char
uchar = Char
'\8855', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\otimes"),(Text
"unicode-math",Text
"\\otimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"multiply sign in circle"}
, Record {uchar :: Char
uchar = Char
'\8856', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\oslash"),(Text
"unicode-math",Text
"\\oslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"solidus in circle"}
, Record {uchar :: Char
uchar = Char
'\8857', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\odot"),(Text
"unicode-math",Text
"\\odot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"middle dot in circle"}
, Record {uchar :: Char
uchar = Char
'\8858', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\circledcirc"),(Text
"unicode-math",Text
"\\circledcirc")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"small circle in circle"}
, Record {uchar :: Char
uchar = Char
'\8859', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\circledast"),(Text
"unicode-math",Text
"\\circledast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"asterisk in circle"}
, Record {uchar :: Char
uchar = Char
'\8860', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledequal")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"equal in circle"}
, Record {uchar :: Char
uchar = Char
'\8861', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\circleddash"),(Text
"unicode-math",Text
"\\circleddash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"hyphen in circle"}
, Record {uchar :: Char
uchar = Char
'\8862', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\boxplus"),(Text
"unicode-math",Text
"\\boxplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"plus sign in box"}
, Record {uchar :: Char
uchar = Char
'\8863', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\boxminus"),(Text
"unicode-math",Text
"\\boxminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"minus sign in box"}
, Record {uchar :: Char
uchar = Char
'\8864', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\boxtimes"),(Text
"unicode-math",Text
"\\boxtimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"multiply sign in box"}
, Record {uchar :: Char
uchar = Char
'\8865', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\boxdot"),(Text
"stmaryrd",Text
"\\boxdot"),(Text
"unicode-math",Text
"\\boxdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"/dotsquare /boxdot b: small dot in box"}
, Record {uchar :: Char
uchar = Char
'\8866', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\vdash"),(Text
"unicode-math",Text
"\\vdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHT TACK, proves, implies, yields, (vertical, dash)"}
, Record {uchar :: Char
uchar = Char
'\8867', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\dashv"),(Text
"unicode-math",Text
"\\dashv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT TACK, non-theorem, does not yield, (dash, vertical)"}
, Record {uchar :: Char
uchar = Char
'\8868', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\top"),(Text
"unicode-math",Text
"\\top")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWN TACK, top"}
, Record {uchar :: Char
uchar = Char
'\8869', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bot"),(Text
"unicode-math",Text
"\\bot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UP TACK, bottom"}
, Record {uchar :: Char
uchar = Char
'\8870', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\vdash"),(Text
"unicode-math",Text
"\\assert")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ASSERTION (vertical, short dash)"}
, Record {uchar :: Char
uchar = Char
'\8871', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\models"),(Text
"unicode-math",Text
"\\models")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"MODELS (vertical, short double dash)"}
, Record {uchar :: Char
uchar = Char
'\8872', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\vDash"),(Text
"fourier",Text
"\\vDash"),(Text
"unicode-math",Text
"\\vDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TRUE (vertical, double dash)"}
, Record {uchar :: Char
uchar = Char
'\8873', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Vdash"),(Text
"unicode-math",Text
"\\Vdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"double vertical, dash"}
, Record {uchar :: Char
uchar = Char
'\8874', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Vvdash"),(Text
"unicode-math",Text
"\\Vvdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"triple vertical, dash"}
, Record {uchar :: Char
uchar = Char
'\8875', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\VDash"),(Text
"txfonts",Text
"\\VDash"),(Text
"unicode-math",Text
"\\VDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"double vert, double dash"}
, Record {uchar :: Char
uchar = Char
'\8876', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nvdash"),(Text
"unicode-math",Text
"\\nvdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not vertical, dash"}
, Record {uchar :: Char
uchar = Char
'\8877', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nvDash"),(Text
"fourier",Text
"\\nvDash"),(Text
"unicode-math",Text
"\\nvDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not vertical, double dash"}
, Record {uchar :: Char
uchar = Char
'\8878', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nVdash"),(Text
"unicode-math",Text
"\\nVdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not double vertical, dash"}
, Record {uchar :: Char
uchar = Char
'\8879', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nVDash"),(Text
"unicode-math",Text
"\\nVDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not double vert, double dash"}
, Record {uchar :: Char
uchar = Char
'\8880', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\prurel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"element PRECEDES UNDER RELATION"}
, Record {uchar :: Char
uchar = Char
'\8881', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\scurel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS UNDER RELATION"}
, Record {uchar :: Char
uchar = Char
'\8882', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\vartriangleleft"),(Text
"unicode-math",Text
"\\vartriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left triangle, open, variant"}
, Record {uchar :: Char
uchar = Char
'\8883', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\vartriangleright"),(Text
"unicode-math",Text
"\\vartriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right triangle, open, variant"}
, Record {uchar :: Char
uchar = Char
'\8884', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\trianglelefteq"),(Text
"wrisym",Text
"\\unlhd"),(Text
"unicode-math",Text
"\\trianglelefteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left triangle, equals"}
, Record {uchar :: Char
uchar = Char
'\8885', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\trianglerighteq"),(Text
"wrisym",Text
"\\unrhd"),(Text
"unicode-math",Text
"\\trianglerighteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right triangle, equals"}
, Record {uchar :: Char
uchar = Char
'\8886', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\multimapdotbothA"),(Text
"unicode-math",Text
"\\origof")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ORIGINAL OF"}
, Record {uchar :: Char
uchar = Char
'\8887', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\multimapdotbothB"),(Text
"unicode-math",Text
"\\imageof")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"IMAGE OF"}
, Record {uchar :: Char
uchar = Char
'\8888', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\multimap"),(Text
"unicode-math",Text
"\\multimap")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"/MULTIMAP a:"}
, Record {uchar :: Char
uchar = Char
'\8889', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hermitmatrix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HERMITIAN CONJUGATE MATRIX"}
, Record {uchar :: Char
uchar = Char
'\8890', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\intercal"),(Text
"fourier",Text
"\\intercal"),(Text
"unicode-math",Text
"\\intercal")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"intercal"}
, Record {uchar :: Char
uchar = Char
'\8891', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\veebar"),(Text
"unicode-math",Text
"\\veebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"logical or, bar below (large vee); exclusive disjunction"}
, Record {uchar :: Char
uchar = Char
'\8892', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\barwedge"),(Text
"unicode-math",Text
"\\barwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"logical NAND (bar over wedge)"}
, Record {uchar :: Char
uchar = Char
'\8893', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\barvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"bar, vee (large vee)"}
, Record {uchar :: Char
uchar = Char
'\8894', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measuredrightangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"right angle-measured [with arc]"}
, Record {uchar :: Char
uchar = Char
'\8895', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varlrtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\8896', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigwedge"),(Text
"unicode-math",Text
"\\bigwedge")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"logical or operator"}
, Record {uchar :: Char
uchar = Char
'\8897', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigvee"),(Text
"unicode-math",Text
"\\bigvee")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"logical and operator"}
, Record {uchar :: Char
uchar = Char
'\8898', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigcap"),(Text
"oz",Text
"\\dint"),(Text
"unicode-math",Text
"\\bigcap")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"\\dinter (oz), intersection operator"}
, Record {uchar :: Char
uchar = Char
'\8899', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigcup"),(Text
"oz",Text
"\\duni"),(Text
"unicode-math",Text
"\\bigcup")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"\\dunion (oz), union operator"}
, Record {uchar :: Char
uchar = Char
'\8900', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\diamond"),(Text
"unicode-math",Text
"\\smwhtdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DIAMOND OPERATOR (white diamond)"}
, Record {uchar :: Char
uchar = Char
'\8901', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\cdot"),(Text
"unicode-math",Text
"\\cdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOT OPERATOR (small middle dot)"}
, Record {uchar :: Char
uchar = Char
'\8902', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\star"),(Text
"unicode-math",Text
"\\star")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"small star, filled, low"}
, Record {uchar :: Char
uchar = Char
'\8903', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\divideontimes"),(Text
"unicode-math",Text
"\\divideontimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"division on times"}
, Record {uchar :: Char
uchar = Char
'\8904', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bowtie"),(Text
"txfonts",Text
"\\lrtimes"),(Text
"unicode-math",Text
"\\bowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"BOWTIE"}
, Record {uchar :: Char
uchar = Char
'\8905', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ltimes"),(Text
"unicode-math",Text
"\\ltimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"times sign, left closed"}
, Record {uchar :: Char
uchar = Char
'\8906', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\rtimes"),(Text
"unicode-math",Text
"\\rtimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"times sign, right closed"}
, Record {uchar :: Char
uchar = Char
'\8907', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leftthreetimes"),(Text
"unicode-math",Text
"\\leftthreetimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LEFT SEMIDIRECT PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\8908', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\rightthreetimes"),(Text
"unicode-math",Text
"\\rightthreetimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"RIGHT SEMIDIRECT PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\8909', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\backsimeq"),(Text
"unicode-math",Text
"\\backsimeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"reverse similar, equals"}
, Record {uchar :: Char
uchar = Char
'\8910', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\curlyvee"),(Text
"unicode-math",Text
"\\curlyvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CURLY LOGICAL OR"}
, Record {uchar :: Char
uchar = Char
'\8911', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\curlywedge"),(Text
"unicode-math",Text
"\\curlywedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CURLY LOGICAL AND"}
, Record {uchar :: Char
uchar = Char
'\8912', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Subset"),(Text
"unicode-math",Text
"\\Subset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE SUBSET"}
, Record {uchar :: Char
uchar = Char
'\8913', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Supset"),(Text
"unicode-math",Text
"\\Supset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE SUPERSET"}
, Record {uchar :: Char
uchar = Char
'\8914', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Cap"),(Text
"unicode-math",Text
"\\Cap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"/cap /doublecap b: DOUBLE INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\8915', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Cup"),(Text
"unicode-math",Text
"\\Cup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"/cup /doublecup b: DOUBLE UNION"}
, Record {uchar :: Char
uchar = Char
'\8916', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\pitchfork"),(Text
"unicode-math",Text
"\\pitchfork")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PITCHFORK"}
, Record {uchar :: Char
uchar = Char
'\8917', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\hash"),(Text
"unicode-math",Text
"\\equalparallel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"parallel, equal; equal or parallel"}
, Record {uchar :: Char
uchar = Char
'\8918', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lessdot"),(Text
"unicode-math",Text
"\\lessdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"less than, with dot"}
, Record {uchar :: Char
uchar = Char
'\8919', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gtrdot"),(Text
"unicode-math",Text
"\\gtrdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"greater than, with dot"}
, Record {uchar :: Char
uchar = Char
'\8920', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lll"),(Text
"unicode-math",Text
"\\lll")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"triple less-than"}
, Record {uchar :: Char
uchar = Char
'\8921', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ggg"),(Text
"unicode-math",Text
"\\ggg")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"triple greater-than"}
, Record {uchar :: Char
uchar = Char
'\8922', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lesseqgtr"),(Text
"unicode-math",Text
"\\lesseqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"less, equals, greater"}
, Record {uchar :: Char
uchar = Char
'\8923', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gtreqless"),(Text
"unicode-math",Text
"\\gtreqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"greater, equals, less"}
, Record {uchar :: Char
uchar = Char
'\8924', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equal-or-less"}
, Record {uchar :: Char
uchar = Char
'\8925', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"equal-or-greater"}
, Record {uchar :: Char
uchar = Char
'\8926', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\curlyeqprec"),(Text
"unicode-math",Text
"\\curlyeqprec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"curly equals, precedes"}
, Record {uchar :: Char
uchar = Char
'\8927', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\curlyeqsucc"),(Text
"unicode-math",Text
"\\curlyeqsucc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"curly equals, succeeds"}
, Record {uchar :: Char
uchar = Char
'\8928', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\npreceq"),(Text
"wrisym",Text
"\\npreceq"),(Text
"unicode-math",Text
"\\npreccurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOES NOT PRECEDE OR EQUAL"}
, Record {uchar :: Char
uchar = Char
'\8929', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\nsucceq"),(Text
"wrisym",Text
"\\nsucceq"),(Text
"unicode-math",Text
"\\nsucccurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not succeeds, curly equals"}
, Record {uchar :: Char
uchar = Char
'\8930', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\nsqsubseteq"),(Text
"unicode-math",Text
"\\nsqsubseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not, square subset, equals"}
, Record {uchar :: Char
uchar = Char
'\8931', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\nsqsupseteq"),(Text
"unicode-math",Text
"\\nsqsupseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not, square superset, equals"}
, Record {uchar :: Char
uchar = Char
'\8932', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sqsubsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"square subset, not equals"}
, Record {uchar :: Char
uchar = Char
'\8933', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sqsupsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"square superset, not equals"}
, Record {uchar :: Char
uchar = Char
'\8934', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lnsim"),(Text
"unicode-math",Text
"\\lnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"less, not similar"}
, Record {uchar :: Char
uchar = Char
'\8935', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gnsim"),(Text
"unicode-math",Text
"\\gnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"greater, not similar"}
, Record {uchar :: Char
uchar = Char
'\8936', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\precnsim"),(Text
"unicode-math",Text
"\\precnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"precedes, not similar"}
, Record {uchar :: Char
uchar = Char
'\8937', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\succnsim"),(Text
"unicode-math",Text
"\\succnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"succeeds, not similar"}
, Record {uchar :: Char
uchar = Char
'\8938', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ntriangleleft"),(Text
"wrisym",Text
"\\NotLeftTriangle"),(Text
"unicode-math",Text
"\\ntriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not left triangle"}
, Record {uchar :: Char
uchar = Char
'\8939', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ntriangleright"),(Text
"wrisym",Text
"\\NotRightTriangle"),(Text
"unicode-math",Text
"\\ntriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not right triangle"}
, Record {uchar :: Char
uchar = Char
'\8940', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ntrianglelefteq"),(Text
"wrisym",Text
"\\nunlhd"),(Text
"unicode-math",Text
"\\ntrianglelefteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not left triangle, equals"}
, Record {uchar :: Char
uchar = Char
'\8941', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\ntrianglerighteq"),(Text
"wrisym",Text
"\\nunrhd"),(Text
"unicode-math",Text
"\\ntrianglerighteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"not right triangle, equals"}
, Record {uchar :: Char
uchar = Char
'\8942', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\vdots"),(Text
"unicode-math",Text
"\\vdots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"VERTICAL ELLIPSIS"}
, Record {uchar :: Char
uchar = Char
'\8943', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\cdots"),(Text
"unicode-math",Text
"\\unicodecdots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"three dots, centered"}
, Record {uchar :: Char
uchar = Char
'\8944', commands :: [(Text, Text)]
commands = [(Text
"mathdots",Text
"\\iddots"),(Text
"yhmath",Text
"\\adots"),(Text
"unicode-math",Text
"\\adots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"three dots, ascending"}
, Record {uchar :: Char
uchar = Char
'\8945', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\ddots"),(Text
"unicode-math",Text
"\\ddots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"three dots, descending"}
, Record {uchar :: Char
uchar = Char
'\8946', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\disin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF WITH LONG HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8947', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varisins")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8948', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\isins")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SMALL ELEMENT OF WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8949', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\isindot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\8950', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\barin"),(Text
"unicode-math",Text
"\\varisinobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\8951', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\isinobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SMALL ELEMENT OF WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\8952', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\isinvb")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\8953', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\isinE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF WITH TWO HORIZONTAL STROKES"}
, Record {uchar :: Char
uchar = Char
'\8954', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nisd")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CONTAINS WITH LONG HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8955', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varnis")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CONTAINS WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8956', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nis")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SMALL CONTAINS WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\8957', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varniobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CONTAINS WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\8958', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\niobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SMALL CONTAINS WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\8959', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{E}"),(Text
"unicode-math",Text
"\\bagmember")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"Z NOTATION BAG MEMBERSHIP"}
, Record {uchar :: Char
uchar = Char
'\8960', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\diameter"),(Text
"amssymb",Text
"\\varnothing"),(Text
"unicode-math",Text
"\\diameter")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIAMETER SIGN"}
, Record {uchar :: Char
uchar = Char
'\8962', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\house")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HOUSE"}
, Record {uchar :: Char
uchar = Char
'\8965', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\barwedge"),(Text
"unicode-math",Text
"\\varbarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PROJECTIVE (bar over small wedge) not nand"}
, Record {uchar :: Char
uchar = Char
'\8966', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\doublebarwedge"),(Text
"unicode-math",Text
"\\vardoublebarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PERSPECTIVE (double bar over small wedge)"}
, Record {uchar :: Char
uchar = Char
'\8968', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\lceil"),(Text
"unicode-math",Text
"\\lceil")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT CEILING"}
, Record {uchar :: Char
uchar = Char
'\8969', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rceil"),(Text
"unicode-math",Text
"\\rceil")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT CEILING"}
, Record {uchar :: Char
uchar = Char
'\8970', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\lfloor"),(Text
"unicode-math",Text
"\\lfloor")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT FLOOR"}
, Record {uchar :: Char
uchar = Char
'\8971', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rfloor"),(Text
"unicode-math",Text
"\\rfloor")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT FLOOR"}
, Record {uchar :: Char
uchar = Char
'\8976', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\invneg"),(Text
"unicode-math",Text
"\\invnot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"reverse not"}
, Record {uchar :: Char
uchar = Char
'\8977', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\wasylozenge"),(Text
"unicode-math",Text
"\\sqlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE LOZENGE"}
, Record {uchar :: Char
uchar = Char
'\8978', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\profline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"profile of a line"}
, Record {uchar :: Char
uchar = Char
'\8979', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\profsurf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"profile of a surface"}
, Record {uchar :: Char
uchar = Char
'\8983', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\viewdata")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"VIEWDATA SQUARE"}
, Record {uchar :: Char
uchar = Char
'\8985', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\turnednot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TURNED NOT SIGN"}
, Record {uchar :: Char
uchar = Char
'\8988', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\ulcorner"),(Text
"unicode-math",Text
"\\ulcorner")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"upper left corner"}
, Record {uchar :: Char
uchar = Char
'\8989', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\urcorner"),(Text
"unicode-math",Text
"\\urcorner")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"upper right corner"}
, Record {uchar :: Char
uchar = Char
'\8990', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\llcorner"),(Text
"unicode-math",Text
"\\llcorner")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"lower left corner"}
, Record {uchar :: Char
uchar = Char
'\8991', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\lrcorner"),(Text
"unicode-math",Text
"\\lrcorner")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"lower right corner"}
, Record {uchar :: Char
uchar = Char
'\8992', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\inttop")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TOP HALF INTEGRAL"}
, Record {uchar :: Char
uchar = Char
'\8993', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intbottom")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BOTTOM HALF INTEGRAL"}
, Record {uchar :: Char
uchar = Char
'\8994', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\frown"),(Text
"base",Text
"\\smallfrown"),(Text
"unicode-math",Text
"\\frown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"FROWN (down curve)"}
, Record {uchar :: Char
uchar = Char
'\8995', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\smile"),(Text
"base",Text
"\\smallsmile"),(Text
"unicode-math",Text
"\\smile")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SMILE (up curve)"}
, Record {uchar :: Char
uchar = Char
'\9001', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\langle"),(Text
"unicode",Text
"\\langle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"Left angle bracket"}
, Record {uchar :: Char
uchar = Char
'\9002', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rangle"),(Text
"unicode",Text
"\\rangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"Right angle bracket"}
, Record {uchar :: Char
uchar = Char
'\9004', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varhexagonlrbonds")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"six carbon ring, corner down, double bonds lower right etc"}
, Record {uchar :: Char
uchar = Char
'\9010', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\conictaper")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CONICAL TAPER"}
, Record {uchar :: Char
uchar = Char
'\9014', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\topbot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL I-BEAM, top and bottom"}
, Record {uchar :: Char
uchar = Char
'\9015', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL SQUISH QUAD"}
, Record {uchar :: Char
uchar = Char
'\9016', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD EQUAL"}
, Record {uchar :: Char
uchar = Char
'\9017', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLinv")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD DIVIDE"}
, Record {uchar :: Char
uchar = Char
'\9018', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\9019', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD JOT"}
, Record {uchar :: Char
uchar = Char
'\9020', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLcirc{\\APLbox}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9021', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLvert{\\Circle}"),(Text
"unicode-math",Text
"\\obar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"x \\obar (stmaryrd), APL FUNCTIONAL SYMBOL CIRCLE STILE, circle with vertical bar"}
, Record {uchar :: Char
uchar = Char
'\9022', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLcirc{\\Circle}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL CIRCLE JOT"}
, Record {uchar :: Char
uchar = Char
'\9023', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\notslash"),(Text
"unicode-math",Text
"\\APLnotslash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL SLASH BAR, solidus, bar through"}
, Record {uchar :: Char
uchar = Char
'\9024', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\notbackslash"),(Text
"unicode-math",Text
"\\APLnotbackslash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL BACKSLASH BAR"}
, Record {uchar :: Char
uchar = Char
'\9025', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD SLASH"}
, Record {uchar :: Char
uchar = Char
'\9026', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD BACKSLASH"}
, Record {uchar :: Char
uchar = Char
'\9027', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\9028', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\9029', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL LEFTWARDS VANE"}
, Record {uchar :: Char
uchar = Char
'\9030', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL RIGHTWARDS VANE"}
, Record {uchar :: Char
uchar = Char
'\9031', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLleftarrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\9032', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLrightarrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\9033', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL CIRCLE BACKSLASH"}
, Record {uchar :: Char
uchar = Char
'\9034', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DOWN TACK UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9035', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLvert{\\APLup}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DELTA STILE"}
, Record {uchar :: Char
uchar = Char
'\9036', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD DOWN CARET"}
, Record {uchar :: Char
uchar = Char
'\9037', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD DELTA"}
, Record {uchar :: Char
uchar = Char
'\9038', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DOWN TACK JOT"}
, Record {uchar :: Char
uchar = Char
'\9039', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL UPWARDS VANE"}
, Record {uchar :: Char
uchar = Char
'\9040', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLuparrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD UPWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\9041', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL UP TACK OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\9042', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLvert{\\APLdown}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DEL STILE"}
, Record {uchar :: Char
uchar = Char
'\9043', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\APLboxupcaret")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD UP CARET"}
, Record {uchar :: Char
uchar = Char
'\9044', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD DEL"}
, Record {uchar :: Char
uchar = Char
'\9045', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL UP TACK JOT"}
, Record {uchar :: Char
uchar = Char
'\9046', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DOWNWARDS VANE"}
, Record {uchar :: Char
uchar = Char
'\9047', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLdownarrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD DOWNWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\9048', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUOTE UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9049', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DELTA UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9050', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DIAMOND UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9051', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL JOT UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9052', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL CIRCLE UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9053', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLcomment")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL UP SHOE JOT"}
, Record {uchar :: Char
uchar = Char
'\9054', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLinput")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUOTE QUAD"}
, Record {uchar :: Char
uchar = Char
'\9055', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLlog")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL CIRCLE STAR"}
, Record {uchar :: Char
uchar = Char
'\9056', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD COLON"}
, Record {uchar :: Char
uchar = Char
'\9057', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL UP TACK DIAERESIS"}
, Record {uchar :: Char
uchar = Char
'\9058', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DEL DIAERESIS"}
, Record {uchar :: Char
uchar = Char
'\9059', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL STAR DIAERESIS"}
, Record {uchar :: Char
uchar = Char
'\9060', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL JOT DIAERESIS"}
, Record {uchar :: Char
uchar = Char
'\9061', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL CIRCLE DIAERESIS"}
, Record {uchar :: Char
uchar = Char
'\9062', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DOWN SHOE STILE"}
, Record {uchar :: Char
uchar = Char
'\9063', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL LEFT SHOE STILE"}
, Record {uchar :: Char
uchar = Char
'\9064', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL TILDE DIAERESIS"}
, Record {uchar :: Char
uchar = Char
'\9065', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL GREATER-THAN DIAERESIS"}
, Record {uchar :: Char
uchar = Char
'\9066', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL COMMA BAR"}
, Record {uchar :: Char
uchar = Char
'\9067', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\APLnot{\\APLdown}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DEL TILDE"}
, Record {uchar :: Char
uchar = Char
'\9068', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL ZILDE"}
, Record {uchar :: Char
uchar = Char
'\9069', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL STILE TILDE"}
, Record {uchar :: Char
uchar = Char
'\9070', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL SEMICOLON UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9071', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD NOT EQUAL"}
, Record {uchar :: Char
uchar = Char
'\9072', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\APLboxquestion")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL QUAD QUESTION"}
, Record {uchar :: Char
uchar = Char
'\9073', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL DOWN CARET TILDE"}
, Record {uchar :: Char
uchar = Char
'\9074', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL UP CARET TILDE"}
, Record {uchar :: Char
uchar = Char
'\9075', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL IOTA"}
, Record {uchar :: Char
uchar = Char
'\9076', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL RHO"}
, Record {uchar :: Char
uchar = Char
'\9077', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\9078', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL ALPHA UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9079', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL EPSILON UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9080', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL IOTA UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9081', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"APL FUNCTIONAL SYMBOL OMEGA UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\9084', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rangledownzigzagarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT ANGLE WITH DOWNWARDS ZIGZAG ARROW"}
, Record {uchar :: Char
uchar = Char
'\9108', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hexagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"horizontal benzene ring [hexagon flat open]"}
, Record {uchar :: Char
uchar = Char
'\9115', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lparenuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT PARENTHESIS UPPER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9116', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lparenextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT PARENTHESIS EXTENSION"}
, Record {uchar :: Char
uchar = Char
'\9117', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lparenlend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT PARENTHESIS LOWER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9118', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rparenuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT PARENTHESIS UPPER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9119', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rparenextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT PARENTHESIS EXTENSION"}
, Record {uchar :: Char
uchar = Char
'\9120', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rparenlend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT PARENTHESIS LOWER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9121', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbrackuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT SQUARE BRACKET UPPER CORNER"}
, Record {uchar :: Char
uchar = Char
'\9122', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbrackextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT SQUARE BRACKET EXTENSION"}
, Record {uchar :: Char
uchar = Char
'\9123', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbracklend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT SQUARE BRACKET LOWER CORNER"}
, Record {uchar :: Char
uchar = Char
'\9124', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbrackuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT SQUARE BRACKET UPPER CORNER"}
, Record {uchar :: Char
uchar = Char
'\9125', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbrackextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT SQUARE BRACKET EXTENSION"}
, Record {uchar :: Char
uchar = Char
'\9126', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbracklend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT SQUARE BRACKET LOWER CORNER"}
, Record {uchar :: Char
uchar = Char
'\9127', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbraceuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT CURLY BRACKET UPPER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9128', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbracemid")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT CURLY BRACKET MIDDLE PIECE"}
, Record {uchar :: Char
uchar = Char
'\9129', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbracelend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT CURLY BRACKET LOWER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9130', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vbraceextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CURLY BRACKET EXTENSION"}
, Record {uchar :: Char
uchar = Char
'\9131', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbraceuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT CURLY BRACKET UPPER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9132', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbracemid")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT CURLY BRACKET MIDDLE PIECE"}
, Record {uchar :: Char
uchar = Char
'\9133', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbracelend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT CURLY BRACKET LOWER HOOK"}
, Record {uchar :: Char
uchar = Char
'\9134', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INTEGRAL EXTENSION"}
, Record {uchar :: Char
uchar = Char
'\9135', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\harrowextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HORIZONTAL LINE EXTENSION (used to extend arrows)"}
, Record {uchar :: Char
uchar = Char
'\9136', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lmoustache")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"? \\lmoustache, UPPER LEFT OR LOWER RIGHT CURLY BRACKET SECTION"}
, Record {uchar :: Char
uchar = Char
'\9137', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rmoustache")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"? \\rmoustache, UPPER RIGHT OR LOWER LEFT CURLY BRACKET SECTION"}
, Record {uchar :: Char
uchar = Char
'\9138', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sumtop")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUMMATION TOP"}
, Record {uchar :: Char
uchar = Char
'\9139', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sumbottom")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUMMATION BOTTOM"}
, Record {uchar :: Char
uchar = Char
'\9140', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\overbracket")], category :: TeXSymbolType
category = TeXSymbolType
TOver, comments :: Text
comments = Text
"TOP SQUARE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\9141', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\underbracket")], category :: TeXSymbolType
category = TeXSymbolType
TUnder, comments :: Text
comments = Text
"BOTTOM SQUARE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\9142', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bbrktbrk")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BOTTOM SQUARE BRACKET OVER TOP SQUARE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\9143', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sqrtbottom")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RADICAL SYMBOL BOTTOM"}
, Record {uchar :: Char
uchar = Char
'\9144', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lvboxline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT VERTICAL BOX LINE"}
, Record {uchar :: Char
uchar = Char
'\9145', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rvboxline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT VERTICAL BOX LINE"}
, Record {uchar :: Char
uchar = Char
'\9166', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varcarriagereturn")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RETURN SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\9168', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"VERTICAL LINE EXTENSION (VERTICAL LINE EXTENSION)"}
, Record {uchar :: Char
uchar = Char
'\9180', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\overparen"),(Text
"yhmath mathabx fourier",Text
"\\wideparen"),(Text
"unicode-math",Text
"\\overparen")], category :: TeXSymbolType
category = TeXSymbolType
TOver, comments :: Text
comments = Text
"TOP PARENTHESIS (mathematical use)"}
, Record {uchar :: Char
uchar = Char
'\9181', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\underparen"),(Text
"unicode-math",Text
"\\underparen")], category :: TeXSymbolType
category = TeXSymbolType
TUnder, comments :: Text
comments = Text
"BOTTOM PARENTHESIS (mathematical use)"}
, Record {uchar :: Char
uchar = Char
'\9182', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\overbrace"),(Text
"unicode-math",Text
"\\overbrace")], category :: TeXSymbolType
category = TeXSymbolType
TOver, comments :: Text
comments = Text
"TOP CURLY BRACKET (mathematical use)"}
, Record {uchar :: Char
uchar = Char
'\9183', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\underbrace"),(Text
"unicode-math",Text
"\\underbrace")], category :: TeXSymbolType
category = TeXSymbolType
TUnder, comments :: Text
comments = Text
"BOTTOM CURLY BRACKET (mathematical use)"}
, Record {uchar :: Char
uchar = Char
'\9184', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\obrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TOP TORTOISE SHELL BRACKET (mathematical use)"}
, Record {uchar :: Char
uchar = Char
'\9185', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ubrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BOTTOM TORTOISE SHELL BRACKET (mathematical use)"}
, Record {uchar :: Char
uchar = Char
'\9186', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\trapezium")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE TRAPEZIUM"}
, Record {uchar :: Char
uchar = Char
'\9187', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\benzenr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BENZENE RING WITH CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9188', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\strns")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"STRAIGHTNESS"}
, Record {uchar :: Char
uchar = Char
'\9189', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\fltns")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FLATNESS"}
, Record {uchar :: Char
uchar = Char
'\9190', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\AC"),(Text
"unicode-math",Text
"\\accurrent")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"AC CURRENT"}
, Record {uchar :: Char
uchar = Char
'\9191', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\elinters")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ELECTRICAL INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\9416', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"oS capital S in circle"}
, Record {uchar :: Char
uchar = Char
'\9478', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bdtriplevdash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"doubly broken vert"}
, Record {uchar :: Char
uchar = Char
'\9600', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blockuphalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPPER HALF BLOCK"}
, Record {uchar :: Char
uchar = Char
'\9604', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blocklowhalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER HALF BLOCK"}
, Record {uchar :: Char
uchar = Char
'\9608', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blockfull")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULL BLOCK"}
, Record {uchar :: Char
uchar = Char
'\9612', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blocklefthalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT HALF BLOCK"}
, Record {uchar :: Char
uchar = Char
'\9616', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blockrighthalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT HALF BLOCK"}
, Record {uchar :: Char
uchar = Char
'\9617', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blockqtrshaded")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"25\\% shaded block"}
, Record {uchar :: Char
uchar = Char
'\9618', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blockhalfshaded")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"50\\% shaded block"}
, Record {uchar :: Char
uchar = Char
'\9619', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blockthreeqtrshaded")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"75\\% shaded block"}
, Record {uchar :: Char
uchar = Char
'\9632', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\blacksquare"),(Text
"unicode-math",Text
"\\mdlgblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, filled"}
, Record {uchar :: Char
uchar = Char
'\9633', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\square"),(Text
"unicode-math",Text
"\\mdlgwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, open"}
, Record {uchar :: Char
uchar = Char
'\9634', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SQUARE WITH ROUNDED CORNERS"}
, Record {uchar :: Char
uchar = Char
'\9635', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackinwhitesquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SQUARE CONTAINING BLACK SMALL SQUARE"}
, Record {uchar :: Char
uchar = Char
'\9636', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarehfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, horizontal rule filled"}
, Record {uchar :: Char
uchar = Char
'\9637', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarevfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, vertical rule filled"}
, Record {uchar :: Char
uchar = Char
'\9638', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarehvfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE WITH ORTHOGONAL CROSSHATCH FILL"}
, Record {uchar :: Char
uchar = Char
'\9639', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarenwsefill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, nw-to-se rule filled"}
, Record {uchar :: Char
uchar = Char
'\9640', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squareneswfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, ne-to-sw rule filled"}
, Record {uchar :: Char
uchar = Char
'\9641', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarecrossfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE WITH DIAGONAL CROSSHATCH FILL"}
, Record {uchar :: Char
uchar = Char
'\9642', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"sq bullet, filled"}
, Record {uchar :: Char
uchar = Char
'\9643', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SMALL SQUARE"}
, Record {uchar :: Char
uchar = Char
'\9644', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hrectangleblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK RECTANGLE"}
, Record {uchar :: Char
uchar = Char
'\9645', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hrectangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"horizontal rectangle, open"}
, Record {uchar :: Char
uchar = Char
'\9646', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vrectangleblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK VERTICAL RECTANGLE"}
, Record {uchar :: Char
uchar = Char
'\9647', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vrectangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"rectangle, white (vertical)"}
, Record {uchar :: Char
uchar = Char
'\9648', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\parallelogramblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK PARALLELOGRAM"}
, Record {uchar :: Char
uchar = Char
'\9649', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\parallelogram")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"parallelogram, open"}
, Record {uchar :: Char
uchar = Char
'\9650', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigblacktriangleup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK UP-POINTING TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\9651', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigtriangleup"),(Text
"amsfonts",Text
"\\triangle"),(Text
"unicode-math",Text
"\\bigtriangleup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"# \\vartriangle (amssymb), big up triangle, open"}
, Record {uchar :: Char
uchar = Char
'\9652', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\blacktriangleup"),(Text
"unicode-math",Text
"\\blacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"up triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9653', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\smalltriangleup"),(Text
"amssymb",Text
"\\vartriangle"),(Text
"unicode-math",Text
"\\vartriangle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"small up triangle, open"}
, Record {uchar :: Char
uchar = Char
'\9654', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\RHD"),(Text
"fourier -mathabx",Text
"\\blacktriangleright"),(Text
"unicode-math",Text
"\\blacktriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"(large) right triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9655', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\rhd"),(Text
"wasysym",Text
"\\rhd"),(Text
"oz",Text
"\\rres"),(Text
"unicode-math",Text
"\\triangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"= \\RightTriangle (wrisym), (large) right triangle, open; z notation range restriction"}
, Record {uchar :: Char
uchar = Char
'\9656', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\blacktriangleright"),(Text
"unicode-math",Text
"\\smallblacktriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"right triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9657', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\smalltriangleright"),(Text
"base",Text
"\\triangleright"),(Text
"unicode-math",Text
"\\smalltriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"x \\triangleright (mathabx), right triangle, open"}
, Record {uchar :: Char
uchar = Char
'\9658', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackpointerright")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK RIGHT-POINTING POINTER"}
, Record {uchar :: Char
uchar = Char
'\9659', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\triangleright"),(Text
"unicode-math",Text
"\\whitepointerright")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE RIGHT-POINTING POINTER"}
, Record {uchar :: Char
uchar = Char
'\9660', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigblacktriangledown")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"big down triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9661', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigtriangledown"),(Text
"unicode-math",Text
"\\bigtriangledown")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"big down triangle, open"}
, Record {uchar :: Char
uchar = Char
'\9662', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\blacktriangledown"),(Text
"unicode-math",Text
"\\blacktriangledown")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"BLACK DOWN-POINTING SMALL TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\9663', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\smalltriangledown"),(Text
"amssymb",Text
"\\triangledown"),(Text
"unicode-math",Text
"\\triangledown")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE DOWN-POINTING SMALL TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\9664', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\LHD"),(Text
"fourier -mathabx",Text
"\\blacktriangleleft"),(Text
"unicode-math",Text
"\\blacktriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"(large) left triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9665', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lhd"),(Text
"wasysym",Text
"\\lhd"),(Text
"oz",Text
"\\dres"),(Text
"unicode-math",Text
"\\triangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"= \\LeftTriangle (wrisym), (large) left triangle, open; z notation domain restriction"}
, Record {uchar :: Char
uchar = Char
'\9666', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\blacktriangleleft"),(Text
"unicode-math",Text
"\\smallblacktriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"left triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9667', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\smalltriangleleft"),(Text
"base",Text
"\\triangleleft"),(Text
"unicode-math",Text
"\\smalltriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"x \\triangleleft (mathabx), left triangle, open"}
, Record {uchar :: Char
uchar = Char
'\9668', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackpointerleft")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK LEFT-POINTING POINTER"}
, Record {uchar :: Char
uchar = Char
'\9669', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\triangleleft"),(Text
"unicode-math",Text
"\\whitepointerleft")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE LEFT-POINTING POINTER"}
, Record {uchar :: Char
uchar = Char
'\9670', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Diamondblack"),(Text
"unicode-math",Text
"\\mdlgblkdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\9671', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Diamond"),(Text
"unicode-math",Text
"\\mdlgwhtdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE DIAMOND; diamond, open"}
, Record {uchar :: Char
uchar = Char
'\9672', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackinwhitediamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE DIAMOND CONTAINING BLACK SMALL DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\9673', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\fisheye")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FISHEYE"}
, Record {uchar :: Char
uchar = Char
'\9674', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lozenge"),(Text
"unicode-math",Text
"\\mdlgwhtlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOZENGE or total mark"}
, Record {uchar :: Char
uchar = Char
'\9675', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\Circle"),(Text
"unicode-math",Text
"\\mdlgwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"medium large circle"}
, Record {uchar :: Char
uchar = Char
'\9676', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dottedcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOTTED CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9677', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circlevertfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLE WITH VERTICAL FILL"}
, Record {uchar :: Char
uchar = Char
'\9678', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\circledcirc"),(Text
"unicode-math",Text
"\\bullseye")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BULLSEYE"}
, Record {uchar :: Char
uchar = Char
'\9679', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\CIRCLE"),(Text
"unicode-math",Text
"\\mdlgblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"circle, filled"}
, Record {uchar :: Char
uchar = Char
'\9680', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\LEFTcircle"),(Text
"unicode-math",Text
"\\circlelefthalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"circle, filled left half [harvey ball]"}
, Record {uchar :: Char
uchar = Char
'\9681', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\RIGHTcircle"),(Text
"unicode-math",Text
"\\circlerighthalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"circle, filled right half"}
, Record {uchar :: Char
uchar = Char
'\9682', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circlebottomhalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"circle, filled bottom half"}
, Record {uchar :: Char
uchar = Char
'\9683', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circletophalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"circle, filled top half"}
, Record {uchar :: Char
uchar = Char
'\9684', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circleurquadblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLE WITH UPPER RIGHT QUADRANT BLACK"}
, Record {uchar :: Char
uchar = Char
'\9685', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackcircleulquadwhite")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLE WITH ALL BUT UPPER LEFT QUADRANT BLACK"}
, Record {uchar :: Char
uchar = Char
'\9686', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\LEFTCIRCLE"),(Text
"unicode-math",Text
"\\blacklefthalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT HALF BLACK CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9687', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\RIGHTCIRCLE"),(Text
"unicode-math",Text
"\\blackrighthalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT HALF BLACK CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9688', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\inversebullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INVERSE BULLET"}
, Record {uchar :: Char
uchar = Char
'\9689', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\inversewhitecircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INVERSE WHITE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9690', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\invwhiteupperhalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPPER HALF INVERSE WHITE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9691', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\invwhitelowerhalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER HALF INVERSE WHITE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9692', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ularc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPPER LEFT QUADRANT CIRCULAR ARC"}
, Record {uchar :: Char
uchar = Char
'\9693', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\urarc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPPER RIGHT QUADRANT CIRCULAR ARC"}
, Record {uchar :: Char
uchar = Char
'\9694', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lrarc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER RIGHT QUADRANT CIRCULAR ARC"}
, Record {uchar :: Char
uchar = Char
'\9695', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\llarc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER LEFT QUADRANT CIRCULAR ARC"}
, Record {uchar :: Char
uchar = Char
'\9696', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\topsemicircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPPER HALF CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9697', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\botsemicircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER HALF CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9698', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lrblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"lower right triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9699', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\llblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"lower left triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9700', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ulblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"upper left triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9701', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\urblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"upper right triangle, filled"}
, Record {uchar :: Char
uchar = Char
'\9702', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE BULLET"}
, Record {uchar :: Char
uchar = Char
'\9703', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squareleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, filled left half"}
, Record {uchar :: Char
uchar = Char
'\9704', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarerightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, filled right half"}
, Record {uchar :: Char
uchar = Char
'\9705', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squareulblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, filled top left corner"}
, Record {uchar :: Char
uchar = Char
'\9706', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarelrblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"square, filled bottom right corner"}
, Record {uchar :: Char
uchar = Char
'\9707', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\boxbar"),(Text
"txfonts",Text
"\\boxbar"),(Text
"unicode-math",Text
"\\boxbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"vertical bar in box"}
, Record {uchar :: Char
uchar = Char
'\9708', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\trianglecdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"triangle with centered dot"}
, Record {uchar :: Char
uchar = Char
'\9709', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangleleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UP-POINTING TRIANGLE WITH LEFT HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\9710', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\trianglerightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UP-POINTING TRIANGLE WITH RIGHT HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\9711', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lgwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LARGE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9712', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squareulquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SQUARE WITH UPPER LEFT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9713', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarellquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SQUARE WITH LOWER LEFT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9714', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarelrquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SQUARE WITH LOWER RIGHT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9715', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squareurquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SQUARE WITH UPPER RIGHT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9716', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circleulquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE CIRCLE WITH UPPER LEFT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9717', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circlellquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE CIRCLE WITH LOWER LEFT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9718', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circlelrquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE CIRCLE WITH LOWER RIGHT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9719', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circleurquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE CIRCLE WITH UPPER RIGHT QUADRANT"}
, Record {uchar :: Char
uchar = Char
'\9720', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ultriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPPER LEFT TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\9721', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\urtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPPER RIGHT TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\9722', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lltriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER LEFT TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\9723', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\square"),(Text
"unicode-math",Text
"\\mdwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE MEDIUM SQUARE"}
, Record {uchar :: Char
uchar = Char
'\9724', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\blacksquare"),(Text
"unicode-math",Text
"\\mdblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK MEDIUM SQUARE"}
, Record {uchar :: Char
uchar = Char
'\9725', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mdsmwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE MEDIUM SMALL SQUARE"}
, Record {uchar :: Char
uchar = Char
'\9726', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mdsmblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK MEDIUM SMALL SQUARE"}
, Record {uchar :: Char
uchar = Char
'\9727', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lrtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER RIGHT TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\9733', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\bigstar"),(Text
"unicode-math",Text
"\\bigstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"star, filled"}
, Record {uchar :: Char
uchar = Char
'\9734', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigwhitestar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"star, open"}
, Record {uchar :: Char
uchar = Char
'\9737', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\Sun"),(Text
"unicode-math",Text
"\\astrosun")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SUN"}
, Record {uchar :: Char
uchar = Char
'\9740', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"text \\CONJUNCTION (wasysym), CONJUNCTION"}
, Record {uchar :: Char
uchar = Char
'\9744', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\Square")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BALLOT BOX"}
, Record {uchar :: Char
uchar = Char
'\9745', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\CheckedBox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"t \\Checkedbox (marvosym), BALLOT BOX WITH CHECK"}
, Record {uchar :: Char
uchar = Char
'\9746', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\XBox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"t \\Crossedbox (marvosym), BALLOT BOX WITH X"}
, Record {uchar :: Char
uchar = Char
'\9749', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\steaming")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HOT BEVERAGE"}
, Record {uchar :: Char
uchar = Char
'\9758', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\pointright")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE RIGHT POINTING INDEX"}
, Record {uchar :: Char
uchar = Char
'\9760', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\skull")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SKULL AND CROSSBONES"}
, Record {uchar :: Char
uchar = Char
'\9761', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\danger")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CAUTION SIGN, dangerous bend"}
, Record {uchar :: Char
uchar = Char
'\9762', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\radiation")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RADIOACTIVE SIGN"}
, Record {uchar :: Char
uchar = Char
'\9763', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\biohazard")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BIOHAZARD SIGN"}
, Record {uchar :: Char
uchar = Char
'\9775', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\yinyang")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"YIN YANG"}
, Record {uchar :: Char
uchar = Char
'\9785', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\frownie"),(Text
"arevmath",Text
"\\sadface")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE FROWNING FACE"}
, Record {uchar :: Char
uchar = Char
'\9786', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\smiley"),(Text
"arevmath",Text
"\\smileface")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SMILING FACE"}
, Record {uchar :: Char
uchar = Char
'\9787', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\blacksmiley"),(Text
"arevmath",Text
"\\invsmileface"),(Text
"unicode-math",Text
"\\blacksmiley")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK SMILING FACE"}
, Record {uchar :: Char
uchar = Char
'\9788', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\sun"),(Text
"unicode-math",Text
"\\sun")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SUN WITH RAYS"}
, Record {uchar :: Char
uchar = Char
'\9789', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\rightmoon"),(Text
"mathabx",Text
"\\rightmoon"),(Text
"unicode-math",Text
"\\rightmoon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FIRST QUARTER MOON"}
, Record {uchar :: Char
uchar = Char
'\9790', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\leftmoon"),(Text
"mathabx",Text
"\\leftmoon"),(Text
"unicode-math",Text
"\\leftmoon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LAST QUARTER MOON"}
, Record {uchar :: Char
uchar = Char
'\9791', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\mercury"),(Text
"mathabx",Text
"\\Mercury")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MERCURY"}
, Record {uchar :: Char
uchar = Char
'\9792', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\female"),(Text
"mathabx",Text
"\\Venus"),(Text
"unicode-math",Text
"\\female")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"= \\girl (mathabx), venus, female"}
, Record {uchar :: Char
uchar = Char
'\9793', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\earth"),(Text
"mathabx",Text
"\\varEarth")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EARTH"}
, Record {uchar :: Char
uchar = Char
'\9794', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\male"),(Text
"mathabx",Text
"\\Mars"),(Text
"unicode-math",Text
"\\male")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"= \\boy (mathabx), mars, male"}
, Record {uchar :: Char
uchar = Char
'\9795', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\jupiter"),(Text
"mathabx",Text
"\\Jupiter")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"JUPITER"}
, Record {uchar :: Char
uchar = Char
'\9796', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\saturn"),(Text
"mathabx",Text
"\\Saturn")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SATURN"}
, Record {uchar :: Char
uchar = Char
'\9797', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\uranus"),(Text
"mathabx",Text
"\\Uranus")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"URANUS"}
, Record {uchar :: Char
uchar = Char
'\9798', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\neptune"),(Text
"mathabx",Text
"\\Neptune")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NEPTUNE"}
, Record {uchar :: Char
uchar = Char
'\9799', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\pluto"),(Text
"mathabx",Text
"\\Pluto")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PLUTO"}
, Record {uchar :: Char
uchar = Char
'\9800', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\aries"),(Text
"mathabx",Text
"\\Aries")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ARIES"}
, Record {uchar :: Char
uchar = Char
'\9801', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\taurus"),(Text
"mathabx",Text
"\\Taurus")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TAURUS"}
, Record {uchar :: Char
uchar = Char
'\9802', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\gemini"),(Text
"mathabx",Text
"\\Gemini")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"GEMINI"}
, Record {uchar :: Char
uchar = Char
'\9803', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\cancer")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CANCER"}
, Record {uchar :: Char
uchar = Char
'\9804', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\leo"),(Text
"mathabx",Text
"\\Leo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEO"}
, Record {uchar :: Char
uchar = Char
'\9805', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\virgo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"VIRGO"}
, Record {uchar :: Char
uchar = Char
'\9806', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\libra"),(Text
"mathabx",Text
"\\Libra")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LIBRA"}
, Record {uchar :: Char
uchar = Char
'\9807', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\scorpio"),(Text
"mathabx",Text
"\\Scorpio")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SCORPIUS"}
, Record {uchar :: Char
uchar = Char
'\9808', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\sagittarius")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SAGITTARIUS"}
, Record {uchar :: Char
uchar = Char
'\9809', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\capricornus")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CAPRICORN"}
, Record {uchar :: Char
uchar = Char
'\9810', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\aquarius")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"AQUARIUS"}
, Record {uchar :: Char
uchar = Char
'\9811', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\pisces")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PISCES"}
, Record {uchar :: Char
uchar = Char
'\9824', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\spadesuit"),(Text
"unicode-math",Text
"\\spadesuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"spades suit symbol"}
, Record {uchar :: Char
uchar = Char
'\9825', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\heartsuit"),(Text
"unicode-math",Text
"\\heartsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"heart suit symbol"}
, Record {uchar :: Char
uchar = Char
'\9826', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\diamondsuit"),(Text
"unicode-math",Text
"\\diamondsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"diamond suit symbol"}
, Record {uchar :: Char
uchar = Char
'\9827', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\clubsuit"),(Text
"unicode-math",Text
"\\clubsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"club suit symbol"}
, Record {uchar :: Char
uchar = Char
'\9828', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\varspadesuit"),(Text
"arevmath",Text
"\\varspade"),(Text
"unicode-math",Text
"\\varspadesuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"spade, white (card suit)"}
, Record {uchar :: Char
uchar = Char
'\9829', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\varheartsuit"),(Text
"arevmath",Text
"\\varheart"),(Text
"unicode-math",Text
"\\varheartsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"filled heart (card suit)"}
, Record {uchar :: Char
uchar = Char
'\9830', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\vardiamondsuit"),(Text
"arevmath",Text
"\\vardiamond"),(Text
"unicode-math",Text
"\\vardiamondsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"filled diamond (card suit)"}
, Record {uchar :: Char
uchar = Char
'\9831', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\varclubsuit"),(Text
"arevmath",Text
"\\varclub"),(Text
"unicode-math",Text
"\\varclubsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"club, white (card suit)"}
, Record {uchar :: Char
uchar = Char
'\9833', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\quarternote"),(Text
"wasysym",Text
"\\quarternote"),(Text
"unicode-math",Text
"\\quarternote")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"music note (sung text sign)"}
, Record {uchar :: Char
uchar = Char
'\9834', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\eighthnote"),(Text
"unicode-math",Text
"\\eighthnote")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EIGHTH NOTE"}
, Record {uchar :: Char
uchar = Char
'\9835', commands :: [(Text, Text)]
commands = [(Text
"wasysym",Text
"\\twonotes"),(Text
"unicode-math",Text
"\\twonotes")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BEAMED EIGHTH NOTES"}
, Record {uchar :: Char
uchar = Char
'\9836', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\sixteenthnote")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BEAMED SIXTEENTH NOTES"}
, Record {uchar :: Char
uchar = Char
'\9837', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\flat"),(Text
"unicode-math",Text
"\\flat")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"musical flat"}
, Record {uchar :: Char
uchar = Char
'\9838', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\natural"),(Text
"unicode-math",Text
"\\natural")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"music natural"}
, Record {uchar :: Char
uchar = Char
'\9839', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sharp"),(Text
"oz",Text
"\\#"),(Text
"unicode-math",Text
"\\sharp")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MUSIC SHARP SIGN, z notation infix bag count"}
, Record {uchar :: Char
uchar = Char
'\9851', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\recycle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK UNIVERSAL RECYCLING SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\9854', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\acidfree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PERMANENT PAPER SIGN"}
, Record {uchar :: Char
uchar = Char
'\9856', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dicei")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIE FACE-1"}
, Record {uchar :: Char
uchar = Char
'\9857', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diceii")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIE FACE-2"}
, Record {uchar :: Char
uchar = Char
'\9858', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diceiii")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIE FACE-3"}
, Record {uchar :: Char
uchar = Char
'\9859', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diceiv")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIE FACE-4"}
, Record {uchar :: Char
uchar = Char
'\9860', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dicev")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIE FACE-5"}
, Record {uchar :: Char
uchar = Char
'\9861', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dicevi")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIE FACE-6"}
, Record {uchar :: Char
uchar = Char
'\9862', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledrightdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE CIRCLE WITH DOT RIGHT"}
, Record {uchar :: Char
uchar = Char
'\9863', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledtwodots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE CIRCLE WITH TWO DOTS"}
, Record {uchar :: Char
uchar = Char
'\9864', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackcircledrightdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK CIRCLE WITH WHITE DOT RIGHT"}
, Record {uchar :: Char
uchar = Char
'\9865', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackcircledtwodots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK CIRCLE WITH TWO WHITE DOTS"}
, Record {uchar :: Char
uchar = Char
'\9875', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\anchor")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ANCHOR"}
, Record {uchar :: Char
uchar = Char
'\9876', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\swords")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CROSSED SWORDS"}
, Record {uchar :: Char
uchar = Char
'\9888', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\warning")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WARNING SIGN"}
, Record {uchar :: Char
uchar = Char
'\9893', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Hermaphrodite")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MALE AND FEMALE SIGN"}
, Record {uchar :: Char
uchar = Char
'\9898', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\medcirc"),(Text
"unicode-math",Text
"\\mdwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEDIUM WHITE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9899', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\medbullet"),(Text
"unicode-math",Text
"\\mdblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEDIUM BLACK CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9900', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mdsmwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEDIUM SMALL WHITE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\9906', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\neuter")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NEUTER"}
, Record {uchar :: Char
uchar = Char
'\9998', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\pencil")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LOWER RIGHT PENCIL"}
, Record {uchar :: Char
uchar = Char
'\10003', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\checkmark"),(Text
"arevmath",Text
"\\ballotcheck"),(Text
"unicode-math",Text
"\\checkmark")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"tick, CHECK MARK"}
, Record {uchar :: Char
uchar = Char
'\10007', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\ballotx")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BALLOT X"}
, Record {uchar :: Char
uchar = Char
'\10016', commands :: [(Text, Text)]
commands = [(Text
"amsfonts",Text
"\\maltese"),(Text
"unicode-math",Text
"\\maltese")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MALTESE CROSS"}
, Record {uchar :: Char
uchar = Char
'\10026', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLED WHITE STAR"}
, Record {uchar :: Char
uchar = Char
'\10038', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SIX POINTED BLACK STAR"}
, Record {uchar :: Char
uchar = Char
'\10045', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dingasterisk")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HEAVY TEARDROP-SPOKED ASTERISK"}
, Record {uchar :: Char
uchar = Char
'\10098', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LIGHT LEFT TORTOISE SHELL BRACKET ORNAMENT"}
, Record {uchar :: Char
uchar = Char
'\10099', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"LIGHT RIGHT TORTOISE SHELL BRACKET ORNAMENT"}
, Record {uchar :: Char
uchar = Char
'\10139', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\draftingarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"right arrow with bold head (drafting)"}
, Record {uchar :: Char
uchar = Char
'\10146', commands :: [(Text, Text)]
commands = [(Text
"arevmath",Text
"\\arrowbullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"THREE-D TOP-LIGHTED RIGHTWARDS ARROWHEAD"}
, Record {uchar :: Char
uchar = Char
'\10176', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\threedangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"THREE DIMENSIONAL ANGLE"}
, Record {uchar :: Char
uchar = Char
'\10177', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\whiteinwhitetriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE TRIANGLE CONTAINING SMALL WHITE TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10178', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\perp"),(Text
"unicode-math",Text
"\\perp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PERPENDICULAR"}
, Record {uchar :: Char
uchar = Char
'\10179', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subsetcirc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"OPEN SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10180', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supsetcirc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"OPEN SUPERSET"}
, Record {uchar :: Char
uchar = Char
'\10181', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\Lbag"),(Text
"txfonts",Text
"\\Lbag"),(Text
"stmaryrd -oz",Text
"\\lbag"),(Text
"unicode-math",Text
"\\lbag")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT S-SHAPED BAG DELIMITER"}
, Record {uchar :: Char
uchar = Char
'\10182', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\Rbag"),(Text
"txfonts",Text
"\\Rbag"),(Text
"stmaryrd -oz",Text
"\\rbag"),(Text
"unicode-math",Text
"\\rbag")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT S-SHAPED BAG DELIMITER"}
, Record {uchar :: Char
uchar = Char
'\10183', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\veedot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"OR WITH DOT INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10184', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bsolhsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"REVERSE SOLIDUS PRECEDING SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10185', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\suphsol")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET PRECEDING SOLIDUS"}
, Record {uchar :: Char
uchar = Char
'\10188', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\longdivision")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LONG DIVISION"}
, Record {uchar :: Char
uchar = Char
'\10192', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Diamonddot"),(Text
"unicode-math",Text
"\\diamondcdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE DIAMOND WITH CENTRED DOT"}
, Record {uchar :: Char
uchar = Char
'\10193', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wedgedot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"AND WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10194', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF OPENING UPWARDS"}
, Record {uchar :: Char
uchar = Char
'\10195', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\pullback")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LOWER RIGHT CORNER WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10196', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\pushout")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPPER LEFT CORNER WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10197', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftouterjoin")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LEFT OUTER JOIN"}
, Record {uchar :: Char
uchar = Char
'\10198', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightouterjoin")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"RIGHT OUTER JOIN"}
, Record {uchar :: Char
uchar = Char
'\10199', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\fullouterjoin")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"FULL OUTER JOIN"}
, Record {uchar :: Char
uchar = Char
'\10200', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigbot")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LARGE UP TACK"}
, Record {uchar :: Char
uchar = Char
'\10201', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigtop")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LARGE DOWN TACK"}
, Record {uchar :: Char
uchar = Char
'\10202', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\DashVDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT AND RIGHT DOUBLE TURNSTILE"}
, Record {uchar :: Char
uchar = Char
'\10203', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dashVdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT AND RIGHT TACK"}
, Record {uchar :: Char
uchar = Char
'\10204', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\multimapinv"),(Text
"unicode-math",Text
"\\multimapinv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT MULTIMAP"}
, Record {uchar :: Char
uchar = Char
'\10205', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vlongdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"long left tack"}
, Record {uchar :: Char
uchar = Char
'\10206', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\longdashv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"long right tack"}
, Record {uchar :: Char
uchar = Char
'\10207', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cirbot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UP TACK WITH CIRCLE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10208', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lozengeminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOZENGE DIVIDED BY HORIZONTAL RULE"}
, Record {uchar :: Char
uchar = Char
'\10209', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\concavediamond")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE CONCAVE-SIDED DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\10210', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\concavediamondtickleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE CONCAVE-SIDED DIAMOND WITH LEFTWARDS TICK"}
, Record {uchar :: Char
uchar = Char
'\10211', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\concavediamondtickright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE CONCAVE-SIDED DIAMOND WITH RIGHTWARDS TICK"}
, Record {uchar :: Char
uchar = Char
'\10212', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\whitesquaretickleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE SQUARE WITH LEFTWARDS TICK"}
, Record {uchar :: Char
uchar = Char
'\10213', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\whitesquaretickright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE SQUARE WITH RIGHTWARDS TICK"}
, Record {uchar :: Char
uchar = Char
'\10214', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\llbracket"),(Text
"wrisym",Text
"\\llbracket"),(Text
"kpfonts",Text
"\\llbracket"),(Text
"fourier",Text
"\\llbracket"),(Text
"mathbbol",Text
"\\Lbrack"),(Text
"unicode-math",Text
"\\lBrack")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"= \\lbag (oz -stmaryrd), MATHEMATICAL LEFT WHITE SQUARE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10215', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\rrbracket"),(Text
"wrisym",Text
"\\rrbracket"),(Text
"kpfonts",Text
"\\rrbracket"),(Text
"fourier",Text
"\\rrbracket"),(Text
"mathbbol",Text
"\\Rbrack"),(Text
"unicode-math",Text
"\\rBrack")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"= \\rbag (oz -stmaryrd), MATHEMATICAL RIGHT WHITE SQUARE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10216', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\langle"),(Text
"unicode-math",Text
"\\langle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"MATHEMATICAL LEFT ANGLE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10217', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rangle"),(Text
"unicode-math",Text
"\\rangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"MATHEMATICAL RIGHT ANGLE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10218', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\lang"),(Text
"unicode-math",Text
"\\lAngle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"MATHEMATICAL LEFT DOUBLE ANGLE BRACKET, z notation left chevron bracket"}
, Record {uchar :: Char
uchar = Char
'\10219', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\rang"),(Text
"unicode-math",Text
"\\rAngle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"MATHEMATICAL RIGHT DOUBLE ANGLE BRACKET, z notation right chevron bracket"}
, Record {uchar :: Char
uchar = Char
'\10220', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"MATHEMATICAL LEFT WHITE TORTOISE SHELL BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10221', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"MATHEMATICAL RIGHT WHITE TORTOISE SHELL BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10222', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\lgroup")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"MATHEMATICAL LEFT FLATTENED PARENTHESIS"}
, Record {uchar :: Char
uchar = Char
'\10223', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rgroup")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"MATHEMATICAL RIGHT FLATTENED PARENTHESIS"}
, Record {uchar :: Char
uchar = Char
'\10224', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\UUparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS QUADRUPLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10225', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\DDownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS QUADRUPLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10226', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\acwgapcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ANTICLOCKWISE GAPPED CIRCLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10227', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cwgapcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CLOCKWISE GAPPED CIRCLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10228', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowonoplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHT ARROW WITH CIRCLED PLUS"}
, Record {uchar :: Char
uchar = Char
'\10229', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\longleftarrow"),(Text
"unicode-math",Text
"\\longleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10230', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\longrightarrow"),(Text
"unicode-math",Text
"\\longrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10231', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\longleftrightarrow"),(Text
"unicode-math",Text
"\\longleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG LEFT RIGHT ARROW"}
, Record {uchar :: Char
uchar = Char
'\10232', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Longleftarrow"),(Text
"amsmath",Text
"\\impliedby"),(Text
"unicode-math",Text
"\\Longleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG LEFTWARDS DOUBLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10233', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Longrightarrow"),(Text
"amsmath",Text
"\\implies"),(Text
"unicode-math",Text
"\\Longrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG RIGHTWARDS DOUBLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10234', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\Longleftrightarrow"),(Text
"oz",Text
"\\iff"),(Text
"unicode-math",Text
"\\Longleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG LEFT RIGHT DOUBLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10235', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\longmapsfrom"),(Text
"kpfonts",Text
"\\longmappedfrom"),(Text
"unicode-math",Text
"\\longmapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG LEFTWARDS ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10236', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\longmapsto"),(Text
"unicode-math",Text
"\\longmapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG RIGHTWARDS ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10237', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\Longmapsfrom"),(Text
"kpfonts",Text
"\\Longmappedfrom"),(Text
"unicode-math",Text
"\\Longmapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG LEFTWARDS DOUBLE ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10238', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\Longmapsto"),(Text
"unicode-math",Text
"\\Longmapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG RIGHTWARDS DOUBLE ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10239', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\longrightsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG RIGHTWARDS SQUIGGLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10496', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\psur"),(Text
"oz",Text
"\\psurj"),(Text
"unicode-math",Text
"\\nvtwoheadrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TWO-HEADED ARROW WITH VERTICAL STROKE, z notation partial surjection"}
, Record {uchar :: Char
uchar = Char
'\10497', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nVtwoheadrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TWO-HEADED ARROW WITH DOUBLE VERTICAL STROKE, z notation finite surjection"}
, Record {uchar :: Char
uchar = Char
'\10498', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvLeftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS DOUBLE ARROW WITH VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10499', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvRightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS DOUBLE ARROW WITH VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10500', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvLeftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT RIGHT DOUBLE ARROW WITH VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10501', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twoheadmapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TWO-HEADED ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10502', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\Mapsfrom"),(Text
"kpfonts",Text
"\\Mappedfrom"),(Text
"unicode-math",Text
"\\Mapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS DOUBLE ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10503', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\Mapsto"),(Text
"unicode-math",Text
"\\Mapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS DOUBLE ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10504', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\downarrowbarred")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS ARROW WITH HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10505', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\uparrowbarred")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS ARROW WITH HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10506', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Uuparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS TRIPLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10507', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Ddownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS TRIPLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10508', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS DOUBLE DASH ARROW"}
, Record {uchar :: Char
uchar = Char
'\10509', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS DOUBLE DASH ARROW"}
, Record {uchar :: Char
uchar = Char
'\10510', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftdbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS TRIPLE DASH ARROW"}
, Record {uchar :: Char
uchar = Char
'\10511', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dbkarow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TRIPLE DASH ARROW"}
, Record {uchar :: Char
uchar = Char
'\10512', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\drbkarow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TWO-HEADED TRIPLE DASH ARROW"}
, Record {uchar :: Char
uchar = Char
'\10513', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightdotarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH DOTTED STEM"}
, Record {uchar :: Char
uchar = Char
'\10514', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\UpArrowBar"),(Text
"unicode-math",Text
"\\baruparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS ARROW TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10515', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\DownArrowBar"),(Text
"unicode-math",Text
"\\downarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS ARROW TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10516', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\pinj"),(Text
"unicode-math",Text
"\\nvrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH TAIL WITH VERTICAL STROKE, z notation partial injection"}
, Record {uchar :: Char
uchar = Char
'\10517', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\finj"),(Text
"unicode-math",Text
"\\nVrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE, z notation finite injection"}
, Record {uchar :: Char
uchar = Char
'\10518', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\bij"),(Text
"unicode-math",Text
"\\twoheadrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TWO-HEADED ARROW WITH TAIL, z notation bijection"}
, Record {uchar :: Char
uchar = Char
'\10519', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvtwoheadrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TWO-HEADED ARROW WITH TAIL WITH VERTICAL STROKE, z notation surjective injection"}
, Record {uchar :: Char
uchar = Char
'\10520', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nVtwoheadrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS TWO-HEADED ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE, z notation finite surjective injection"}
, Record {uchar :: Char
uchar = Char
'\10521', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lefttail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW-TAIL"}
, Record {uchar :: Char
uchar = Char
'\10522', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\righttail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW-TAIL"}
, Record {uchar :: Char
uchar = Char
'\10523', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftdbltail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS DOUBLE ARROW-TAIL"}
, Record {uchar :: Char
uchar = Char
'\10524', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightdbltail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS DOUBLE ARROW-TAIL"}
, Record {uchar :: Char
uchar = Char
'\10525', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diamondleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW TO BLACK DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\10526', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW TO BLACK DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\10527', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diamondleftarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW FROM BAR TO BLACK DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\10528', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\barrightarrowdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW FROM BAR TO BLACK DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\10529', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nwsearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NORTH WEST AND SOUTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10530', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\neswarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NORTH EAST AND SOUTH WEST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10531', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hknwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NORTH WEST ARROW WITH HOOK"}
, Record {uchar :: Char
uchar = Char
'\10532', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hknearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NORTH EAST ARROW WITH HOOK"}
, Record {uchar :: Char
uchar = Char
'\10533', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hksearow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SOUTH EAST ARROW WITH HOOK"}
, Record {uchar :: Char
uchar = Char
'\10534', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hkswarow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SOUTH WEST ARROW WITH HOOK"}
, Record {uchar :: Char
uchar = Char
'\10535', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\tona")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NORTH WEST ARROW AND NORTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10536', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\toea")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NORTH EAST ARROW AND SOUTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10537', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\tosa")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SOUTH EAST ARROW AND SOUTH WEST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10538', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\towa")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SOUTH WEST ARROW AND NORTH WEST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10539', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rdiagovfdiag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RISING DIAGONAL CROSSING FALLING DIAGONAL"}
, Record {uchar :: Char
uchar = Char
'\10540', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\fdiagovrdiag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FALLING DIAGONAL CROSSING RISING DIAGONAL"}
, Record {uchar :: Char
uchar = Char
'\10541', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\seovnearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SOUTH EAST ARROW CROSSING NORTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10542', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\neovsearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH EAST ARROW CROSSING SOUTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10543', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\fdiagovnearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FALLING DIAGONAL CROSSING NORTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10544', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rdiagovsearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RISING DIAGONAL CROSSING SOUTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10545', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\neovnwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH EAST ARROW CROSSING NORTH WEST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10546', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nwovnearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH WEST ARROW CROSSING NORTH EAST ARROW"}
, Record {uchar :: Char
uchar = Char
'\10547', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\leadsto"),(Text
"unicode-math",Text
"\\rightcurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"WAVE ARROW POINTING DIRECTLY RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10548', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\uprightcurvearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ARROW POINTING RIGHTWARDS THEN CURVING UPWARDS"}
, Record {uchar :: Char
uchar = Char
'\10549', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\downrightcurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ARROW POINTING RIGHTWARDS THEN CURVING DOWNWARDS"}
, Record {uchar :: Char
uchar = Char
'\10550', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftdowncurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ARROW POINTING DOWNWARDS THEN CURVING LEFTWARDS"}
, Record {uchar :: Char
uchar = Char
'\10551', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightdowncurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ARROW POINTING DOWNWARDS THEN CURVING RIGHTWARDS"}
, Record {uchar :: Char
uchar = Char
'\10552', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cwrightarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHT-SIDE ARC CLOCKWISE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10553', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\acwleftarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT-SIDE ARC ANTICLOCKWISE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10554', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\acwoverarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TOP ARC ANTICLOCKWISE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10555', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\acwunderarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"BOTTOM ARC ANTICLOCKWISE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10556', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\curvearrowrightminus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TOP ARC CLOCKWISE ARROW WITH MINUS"}
, Record {uchar :: Char
uchar = Char
'\10557', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\curvearrowleftplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TOP ARC ANTICLOCKWISE ARROW WITH PLUS"}
, Record {uchar :: Char
uchar = Char
'\10558', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cwundercurvearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LOWER RIGHT SEMICIRCULAR CLOCKWISE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10559', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ccwundercurvearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LOWER LEFT SEMICIRCULAR ANTICLOCKWISE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10560', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\acwcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ANTICLOCKWISE CLOSED CIRCLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10561', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cwcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CLOCKWISE CLOSED CIRCLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\10562', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowshortleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW ABOVE SHORT LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10563', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowshortrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW ABOVE SHORT RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10564', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\shortrightarrowleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SHORT RIGHTWARDS ARROW ABOVE LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10565', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH PLUS BELOW"}
, Record {uchar :: Char
uchar = Char
'\10566', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH PLUS BELOW"}
, Record {uchar :: Char
uchar = Char
'\10567', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowx")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW THROUGH X"}
, Record {uchar :: Char
uchar = Char
'\10568', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftrightarrowcircle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT RIGHT ARROW THROUGH SMALL CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10569', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twoheaduparrowcircle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS TWO-HEADED ARROW FROM SMALL CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10570', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\leftrightharpoon"),(Text
"unicode-math",Text
"\\leftrightharpoonupdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT BARB UP RIGHT BARB DOWN HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10571', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\rightleftharpoon"),(Text
"unicode-math",Text
"\\leftrightharpoondownup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT BARB DOWN RIGHT BARB UP HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10572', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\updownharpoonrightleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UP BARB RIGHT DOWN BARB LEFT HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10573', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\updownharpoonleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UP BARB LEFT DOWN BARB RIGHT HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10574', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\leftrightharpoonup"),(Text
"unicode-math",Text
"\\leftrightharpoonupup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT BARB UP RIGHT BARB UP HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10575', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\rightupdownharpoon"),(Text
"unicode-math",Text
"\\updownharpoonrightright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UP BARB RIGHT DOWN BARB RIGHT HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10576', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\leftrightharpoondown"),(Text
"unicode-math",Text
"\\leftrightharpoondowndown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT BARB DOWN RIGHT BARB DOWN HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10577', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\leftupdownharpoon"),(Text
"unicode-math",Text
"\\updownharpoonleftleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UP BARB LEFT DOWN BARB LEFT HARPOON"}
, Record {uchar :: Char
uchar = Char
'\10578', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftVectorBar"),(Text
"unicode-math",Text
"\\barleftharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB UP TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10579', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightVectorBar"),(Text
"unicode-math",Text
"\\rightharpoonupbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB UP TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10580', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightUpVectorBar"),(Text
"unicode-math",Text
"\\barupharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS HARPOON WITH BARB RIGHT TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10581', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightDownVectorBar"),(Text
"unicode-math",Text
"\\downharpoonrightbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS HARPOON WITH BARB RIGHT TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10582', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\DownLeftVectorBar"),(Text
"unicode-math",Text
"\\barleftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB DOWN TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10583', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\DownRightVectorBar"),(Text
"unicode-math",Text
"\\rightharpoondownbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB DOWN TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10584', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftUpVectorBar"),(Text
"unicode-math",Text
"\\barupharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS HARPOON WITH BARB LEFT TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10585', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftDownVectorBar"),(Text
"unicode-math",Text
"\\downharpoonleftbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS HARPOON WITH BARB LEFT TO BAR"}
, Record {uchar :: Char
uchar = Char
'\10586', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftTeeVector"),(Text
"unicode-math",Text
"\\leftharpoonupbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB UP FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10587', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightTeeVector"),(Text
"unicode-math",Text
"\\barrightharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB UP FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10588', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightUpTeeVector"),(Text
"unicode-math",Text
"\\upharpoonrightbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS HARPOON WITH BARB RIGHT FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10589', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightDownTeeVector"),(Text
"unicode-math",Text
"\\bardownharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS HARPOON WITH BARB RIGHT FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10590', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\DownLeftTeeVector"),(Text
"unicode-math",Text
"\\leftharpoondownbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB DOWN FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10591', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\DownRightTeeVector"),(Text
"unicode-math",Text
"\\barrightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB DOWN FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10592', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftUpTeeVector"),(Text
"unicode-math",Text
"\\upharpoonleftbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS HARPOON WITH BARB LEFT FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10593', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftDownTeeVector"),(Text
"unicode-math",Text
"\\bardownharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS HARPOON WITH BARB LEFT FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\10594', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\leftleftharpoons"),(Text
"unicode-math",Text
"\\leftharpoonsupdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB UP ABOVE LEFTWARDS HARPOON WITH BARB DOWN"}
, Record {uchar :: Char
uchar = Char
'\10595', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\upupharpoons"),(Text
"unicode-math",Text
"\\upharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS HARPOON WITH BARB LEFT BESIDE UPWARDS HARPOON WITH BARB RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10596', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\rightrightharpoons"),(Text
"unicode-math",Text
"\\rightharpoonsupdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB UP ABOVE RIGHTWARDS HARPOON WITH BARB DOWN"}
, Record {uchar :: Char
uchar = Char
'\10597', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\downdownharpoons"),(Text
"unicode-math",Text
"\\downharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS HARPOON WITH BARB LEFT BESIDE DOWNWARDS HARPOON WITH BARB RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10598', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftrightharpoonsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB UP ABOVE RIGHTWARDS HARPOON WITH BARB UP"}
, Record {uchar :: Char
uchar = Char
'\10599', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftrightharpoonsdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB DOWN ABOVE RIGHTWARDS HARPOON WITH BARB DOWN"}
, Record {uchar :: Char
uchar = Char
'\10600', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightleftharpoonsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB UP ABOVE LEFTWARDS HARPOON WITH BARB UP"}
, Record {uchar :: Char
uchar = Char
'\10601', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightleftharpoonsdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB DOWN ABOVE LEFTWARDS HARPOON WITH BARB DOWN"}
, Record {uchar :: Char
uchar = Char
'\10602', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\leftbarharpoon"),(Text
"unicode-math",Text
"\\leftharpoonupdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB UP ABOVE LONG DASH"}
, Record {uchar :: Char
uchar = Char
'\10603', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\barleftharpoon"),(Text
"unicode-math",Text
"\\dashleftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS HARPOON WITH BARB DOWN BELOW LONG DASH"}
, Record {uchar :: Char
uchar = Char
'\10604', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\rightbarharpoon"),(Text
"unicode-math",Text
"\\rightharpoonupdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB UP ABOVE LONG DASH"}
, Record {uchar :: Char
uchar = Char
'\10605', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\barrightharpoon"),(Text
"unicode-math",Text
"\\dashrightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS HARPOON WITH BARB DOWN BELOW LONG DASH"}
, Record {uchar :: Char
uchar = Char
'\10606', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\updownharpoons"),(Text
"wrisym",Text
"\\upequilibrium"),(Text
"unicode-math",Text
"\\updownharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UPWARDS HARPOON WITH BARB LEFT BESIDE DOWNWARDS HARPOON WITH BARB RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10607', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\downupharpoons"),(Text
"wrisym",Text
"\\uprevequilibrium"),(Text
"unicode-math",Text
"\\downupharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWNWARDS HARPOON WITH BARB LEFT BESIDE UPWARDS HARPOON WITH BARB RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10608', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightimply")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHT DOUBLE ARROW WITH ROUNDED HEAD"}
, Record {uchar :: Char
uchar = Char
'\10609', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\equalrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN ABOVE RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10610', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\similarrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TILDE OPERATOR ABOVE RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10611', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW ABOVE TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10612', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW ABOVE TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10613', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW ABOVE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10614', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ltlarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN ABOVE LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10615', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW THROUGH LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10616', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gtrarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN ABOVE RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10617', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subrarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET ABOVE RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10618', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowsubset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW THROUGH SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10619', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\suplarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET ABOVE LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\10620', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\strictfi"),(Text
"unicode-math",Text
"\\leftfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT FISH TAIL"}
, Record {uchar :: Char
uchar = Char
'\10621', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\strictif"),(Text
"unicode-math",Text
"\\rightfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHT FISH TAIL"}
, Record {uchar :: Char
uchar = Char
'\10622', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"UP FISH TAIL"}
, Record {uchar :: Char
uchar = Char
'\10623', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\downfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOWN FISH TAIL"}
, Record {uchar :: Char
uchar = Char
'\10624', commands :: [(Text, Text)]
commands = [(Text
"fourier",Text
"\\VERT"),(Text
"unicode-math",Text
"\\Vvert")], category :: TeXSymbolType
category = TeXSymbolType
Fence, comments :: Text
comments = Text
"TRIPLE VERTICAL BAR DELIMITER"}
, Record {uchar :: Char
uchar = Char
'\10625', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\spot"),(Text
"oz",Text
"\\dot"),(Text
"unicode-math",Text
"\\mdsmblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"Z NOTATION SPOT"}
, Record {uchar :: Char
uchar = Char
'\10626', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\typecolon")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"Z NOTATION TYPE COLON, (present in bbold font but no command)"}
, Record {uchar :: Char
uchar = Char
'\10627', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lBrace")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT WHITE CURLY BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10628', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rBrace")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT WHITE CURLY BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10629', commands :: [(Text, Text)]
commands = [(Text
"mathbbol",Text
"\\Lparen"),(Text
"unicode-math",Text
"\\lParen")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT WHITE PARENTHESIS"}
, Record {uchar :: Char
uchar = Char
'\10630', commands :: [(Text, Text)]
commands = [(Text
"mathbbol",Text
"\\Rparen"),(Text
"unicode-math",Text
"\\rParen")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT WHITE PARENTHESIS"}
, Record {uchar :: Char
uchar = Char
'\10631', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\limg"),(Text
"stmaryrd",Text
"\\llparenthesis"),(Text
"unicode-math",Text
"\\llparenthesis")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"Z NOTATION LEFT IMAGE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10632', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\rimg"),(Text
"stmaryrd",Text
"\\rrparenthesis"),(Text
"unicode-math",Text
"\\rrparenthesis")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"Z NOTATION RIGHT IMAGE BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10633', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\lblot"),(Text
"unicode-math",Text
"\\llangle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"Z NOTATION LEFT BINDING BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10634', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\rblot"),(Text
"unicode-math",Text
"\\rrangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"Z NOTATION RIGHT BINDING BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10635', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbrackubar")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT SQUARE BRACKET WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10636', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbrackubar")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT SQUARE BRACKET WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10637', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbrackultick")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT SQUARE BRACKET WITH TICK IN TOP CORNER"}
, Record {uchar :: Char
uchar = Char
'\10638', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbracklrtick")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT SQUARE BRACKET WITH TICK IN BOTTOM CORNER"}
, Record {uchar :: Char
uchar = Char
'\10639', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbracklltick")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT SQUARE BRACKET WITH TICK IN BOTTOM CORNER"}
, Record {uchar :: Char
uchar = Char
'\10640', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbrackurtick")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT SQUARE BRACKET WITH TICK IN TOP CORNER"}
, Record {uchar :: Char
uchar = Char
'\10641', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\langledot")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT ANGLE BRACKET WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10642', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rangledot")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT ANGLE BRACKET WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10643', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lparenless")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT ARC LESS-THAN BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10644', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rparengtr")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT ARC GREATER-THAN BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10645', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Lparengtr")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"DOUBLE LEFT ARC GREATER-THAN BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10646', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Rparenless")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"DOUBLE RIGHT ARC LESS-THAN BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10647', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lblkbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT BLACK TORTOISE SHELL BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10648', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rblkbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT BLACK TORTOISE SHELL BRACKET"}
, Record {uchar :: Char
uchar = Char
'\10649', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\fourvdots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOTTED FENCE"}
, Record {uchar :: Char
uchar = Char
'\10650', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"VERTICAL ZIGZAG LINE"}
, Record {uchar :: Char
uchar = Char
'\10651', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measuredangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE OPENING LEFT"}
, Record {uchar :: Char
uchar = Char
'\10652', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightanglesqr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHT ANGLE VARIANT WITH SQUARE"}
, Record {uchar :: Char
uchar = Char
'\10653', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightanglemdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED RIGHT ANGLE WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10654', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\angles")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ANGLE WITH S INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10655', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\angdnr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ACUTE ANGLE"}
, Record {uchar :: Char
uchar = Char
'\10656', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gtlpar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SPHERICAL ANGLE OPENING LEFT"}
, Record {uchar :: Char
uchar = Char
'\10657', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sphericalangleup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SPHERICAL ANGLE OPENING UP"}
, Record {uchar :: Char
uchar = Char
'\10658', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\turnangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TURNED ANGLE"}
, Record {uchar :: Char
uchar = Char
'\10659', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\revangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"REVERSED ANGLE"}
, Record {uchar :: Char
uchar = Char
'\10660', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\angleubar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ANGLE WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10661', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\revangleubar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"REVERSED ANGLE WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10662', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wideangledown")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"OBLIQUE ANGLE OPENING UP"}
, Record {uchar :: Char
uchar = Char
'\10663', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wideangleup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"OBLIQUE ANGLE OPENING DOWN"}
, Record {uchar :: Char
uchar = Char
'\10664', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measanglerutone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING UP AND RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10665', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measanglelutonw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING UP AND LEFT"}
, Record {uchar :: Char
uchar = Char
'\10666', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measanglerdtose")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING DOWN AND RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10667', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measangleldtosw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING DOWN AND LEFT"}
, Record {uchar :: Char
uchar = Char
'\10668', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measangleurtone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING RIGHT AND UP"}
, Record {uchar :: Char
uchar = Char
'\10669', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measangleultonw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING LEFT AND UP"}
, Record {uchar :: Char
uchar = Char
'\10670', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measangledrtose")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING RIGHT AND DOWN"}
, Record {uchar :: Char
uchar = Char
'\10671', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\measangledltosw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING LEFT AND DOWN"}
, Record {uchar :: Char
uchar = Char
'\10672', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\revemptyset")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"REVERSED EMPTY SET"}
, Record {uchar :: Char
uchar = Char
'\10673', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\emptysetobar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EMPTY SET WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10674', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\emptysetocirc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EMPTY SET WITH SMALL CIRCLE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10675', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\emptysetoarr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EMPTY SET WITH RIGHT ARROW ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10676', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\emptysetoarrl")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"EMPTY SET WITH LEFT ARROW ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10677', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circlehbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLE WITH HORIZONTAL BAR"}
, Record {uchar :: Char
uchar = Char
'\10678', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED VERTICAL BAR"}
, Record {uchar :: Char
uchar = Char
'\10679', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledparallel")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED PARALLEL"}
, Record {uchar :: Char
uchar = Char
'\10680', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\circledbslash"),(Text
"unicode-math",Text
"\\obslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED REVERSE SOLIDUS"}
, Record {uchar :: Char
uchar = Char
'\10681', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\operp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED PERPENDICULAR"}
, Record {uchar :: Char
uchar = Char
'\10682', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\obot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLE DIVIDED BY HORIZONTAL BAR AND TOP HALF DIVIDED BY VERTICAL BAR"}
, Record {uchar :: Char
uchar = Char
'\10683', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\olcross")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLE WITH SUPERIMPOSED X"}
, Record {uchar :: Char
uchar = Char
'\10684', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\odotslashdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLED ANTICLOCKWISE-ROTATED DIVISION SIGN"}
, Record {uchar :: Char
uchar = Char
'\10685', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\uparrowoncircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UP ARROW THROUGH CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10686', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledwhitebullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLED WHITE BULLET"}
, Record {uchar :: Char
uchar = Char
'\10687', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledbullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLED BULLET"}
, Record {uchar :: Char
uchar = Char
'\10688', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\circledless"),(Text
"unicode-math",Text
"\\olessthan")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10689', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\circledgtr"),(Text
"unicode-math",Text
"\\ogreaterthan")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10690', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cirscir")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLE WITH SMALL CIRCLE TO THE RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10691', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cirE")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"CIRCLE WITH TWO HORIZONTAL STROKES TO THE RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10692', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\boxslash"),(Text
"txfonts",Text
"\\boxslash"),(Text
"unicode-math",Text
"\\boxdiag")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SQUARED RISING DIAGONAL SLASH"}
, Record {uchar :: Char
uchar = Char
'\10693', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\boxbslash"),(Text
"txfonts",Text
"\\boxbslash"),(Text
"unicode-math",Text
"\\boxbslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SQUARED FALLING DIAGONAL SLASH"}
, Record {uchar :: Char
uchar = Char
'\10694', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\boxast"),(Text
"txfonts",Text
"\\boxast"),(Text
"unicode-math",Text
"\\boxast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SQUARED ASTERISK"}
, Record {uchar :: Char
uchar = Char
'\10695', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\boxcircle"),(Text
"unicode-math",Text
"\\boxcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SQUARED SMALL CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10696', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\boxbox"),(Text
"unicode-math",Text
"\\boxbox")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SQUARED SQUARE"}
, Record {uchar :: Char
uchar = Char
'\10697', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\boxonbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TWO JOINED SQUARES"}
, Record {uchar :: Char
uchar = Char
'\10698', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangleodot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TRIANGLE WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10699', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangleubar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TRIANGLE WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10700', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangles")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"S IN TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10701', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangleserifs")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TRIANGLE WITH SERIFS AT BOTTOM"}
, Record {uchar :: Char
uchar = Char
'\10702', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rtriltri")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHT TRIANGLE ABOVE LEFT TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10703', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\LeftTriangleBar"),(Text
"unicode-math",Text
"\\ltrivb")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT TRIANGLE BESIDE VERTICAL BAR"}
, Record {uchar :: Char
uchar = Char
'\10704', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\RightTriangleBar"),(Text
"unicode-math",Text
"\\vbrtri")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"VERTICAL BAR BESIDE RIGHT TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10705', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lfbowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left black bowtie"}
, Record {uchar :: Char
uchar = Char
'\10706', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rfbowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right black bowtie"}
, Record {uchar :: Char
uchar = Char
'\10707', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\fbowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"BLACK BOWTIE"}
, Record {uchar :: Char
uchar = Char
'\10708', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lftimes")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"left black times"}
, Record {uchar :: Char
uchar = Char
'\10709', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rftimes")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"right black times"}
, Record {uchar :: Char
uchar = Char
'\10710', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hourglass")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE HOURGLASS"}
, Record {uchar :: Char
uchar = Char
'\10711', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackhourglass")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"BLACK HOURGLASS"}
, Record {uchar :: Char
uchar = Char
'\10712', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT WIGGLY FENCE"}
, Record {uchar :: Char
uchar = Char
'\10713', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT WIGGLY FENCE"}
, Record {uchar :: Char
uchar = Char
'\10714', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Lvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT DOUBLE WIGGLY FENCE"}
, Record {uchar :: Char
uchar = Char
'\10715', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Rvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT DOUBLE WIGGLY FENCE"}
, Record {uchar :: Char
uchar = Char
'\10716', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\iinfin")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INCOMPLETE INFINITY"}
, Record {uchar :: Char
uchar = Char
'\10717', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\tieinfty")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"TIE OVER INFINITY"}
, Record {uchar :: Char
uchar = Char
'\10718', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvinfty")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"INFINITY NEGATED WITH VERTICAL BAR"}
, Record {uchar :: Char
uchar = Char
'\10719', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\multimapboth"),(Text
"unicode-math",Text
"\\dualmap")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE-ENDED MULTIMAP"}
, Record {uchar :: Char
uchar = Char
'\10720', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\laplac")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE WITH CONTOURED OUTLINE"}
, Record {uchar :: Char
uchar = Char
'\10721', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lrtriangleeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"INCREASES AS"}
, Record {uchar :: Char
uchar = Char
'\10722', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\shuffle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SHUFFLE PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\10723', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eparsl")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN AND SLANTED PARALLEL"}
, Record {uchar :: Char
uchar = Char
'\10724', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smeparsl")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN AND SLANTED PARALLEL WITH TILDE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10725', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqvparsl")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"IDENTICAL TO AND SLANTED PARALLEL"}
, Record {uchar :: Char
uchar = Char
'\10726', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gleichstark")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GLEICH STARK"}
, Record {uchar :: Char
uchar = Char
'\10727', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\thermod")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"THERMODYNAMIC"}
, Record {uchar :: Char
uchar = Char
'\10728', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\downtriangleleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWN-POINTING TRIANGLE WITH LEFT HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\10729', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\downtrianglerightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWN-POINTING TRIANGLE WITH RIGHT HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\10730', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackdiamonddownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK DIAMOND WITH DOWN ARROW"}
, Record {uchar :: Char
uchar = Char
'\10731', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\blacklozenge"),(Text
"unicode-math",Text
"\\mdlgblklozenge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"BLACK LOZENGE"}
, Record {uchar :: Char
uchar = Char
'\10732', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circledownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE CIRCLE WITH DOWN ARROW"}
, Record {uchar :: Char
uchar = Char
'\10733', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blackcircledownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK CIRCLE WITH DOWN ARROW"}
, Record {uchar :: Char
uchar = Char
'\10734', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\errbarsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ERROR-BARRED WHITE SQUARE"}
, Record {uchar :: Char
uchar = Char
'\10735', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\errbarblacksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ERROR-BARRED BLACK SQUARE"}
, Record {uchar :: Char
uchar = Char
'\10736', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\errbardiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ERROR-BARRED WHITE DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\10737', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\errbarblackdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ERROR-BARRED BLACK DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\10738', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\errbarcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ERROR-BARRED WHITE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10739', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\errbarblackcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"ERROR-BARRED BLACK CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10740', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ruledelayed")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RULE-DELAYED"}
, Record {uchar :: Char
uchar = Char
'\10741', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\setminus"),(Text
"unicode-math",Text
"\\setminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"REVERSE SOLIDUS OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10742', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dsol")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SOLIDUS WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10743', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rsolbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"REVERSE SOLIDUS WITH HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10744', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\xsol")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"BIG SOLIDUS"}
, Record {uchar :: Char
uchar = Char
'\10745', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\zhide"),(Text
"oz",Text
"\\hide"),(Text
"unicode-math",Text
"\\xbsol")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"BIG REVERSE SOLIDUS, z notation schema hiding"}
, Record {uchar :: Char
uchar = Char
'\10746', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\doubleplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOUBLE PLUS"}
, Record {uchar :: Char
uchar = Char
'\10747', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\tripleplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TRIPLE PLUS"}
, Record {uchar :: Char
uchar = Char
'\10748', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lcurvyangle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"left pointing curved angle bracket"}
, Record {uchar :: Char
uchar = Char
'\10749', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rcurvyangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"right pointing curved angle bracket"}
, Record {uchar :: Char
uchar = Char
'\10750', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\tplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TINY"}
, Record {uchar :: Char
uchar = Char
'\10751', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\tminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINY"}
, Record {uchar :: Char
uchar = Char
'\10752', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigodot"),(Text
"unicode-math",Text
"\\bigodot")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY CIRCLED DOT OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10753', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigoplus"),(Text
"unicode-math",Text
"\\bigoplus")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY CIRCLED PLUS OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10754', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigotimes"),(Text
"unicode-math",Text
"\\bigotimes")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY CIRCLED TIMES OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10755', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigcupdot")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY UNION OPERATOR WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10756', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\biguplus"),(Text
"unicode-math",Text
"\\biguplus")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY UNION OPERATOR WITH PLUS"}
, Record {uchar :: Char
uchar = Char
'\10757', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\bigsqcap"),(Text
"unicode-math",Text
"\\bigsqcap")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY SQUARE INTERSECTION OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10758', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\bigsqcup"),(Text
"unicode-math",Text
"\\bigsqcup")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY SQUARE UNION OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10759', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\conjquant")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"TWO LOGICAL AND OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10760', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\disjquant")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"TWO LOGICAL OR OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10761', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\varprod"),(Text
"unicode-math",Text
"\\bigtimes")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY TIMES OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10762', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\modtwosum")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MODULO TWO SUM"}
, Record {uchar :: Char
uchar = Char
'\10763', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\sumint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"SUMMATION WITH INTEGRAL"}
, Record {uchar :: Char
uchar = Char
'\10764', commands :: [(Text, Text)]
commands = [(Text
"amsmath",Text
"\\iiiint"),(Text
"esint",Text
"\\iiiint"),(Text
"unicode-math",Text
"\\iiiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"QUADRUPLE INTEGRAL OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10765', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intbar")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"FINITE PART INTEGRAL"}
, Record {uchar :: Char
uchar = Char
'\10766', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intBar")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL WITH DOUBLE STROKE"}
, Record {uchar :: Char
uchar = Char
'\10767', commands :: [(Text, Text)]
commands = [(Text
"esint",Text
"\\fint"),(Text
"wrisym",Text
"\\fint"),(Text
"unicode-math",Text
"\\fint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL AVERAGE WITH SLASH"}
, Record {uchar :: Char
uchar = Char
'\10768', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cirfnint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"CIRCULATION FUNCTION"}
, Record {uchar :: Char
uchar = Char
'\10769', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\awint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"ANTICLOCKWISE INTEGRATION"}
, Record {uchar :: Char
uchar = Char
'\10770', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rppolint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LINE INTEGRATION WITH RECTANGULAR PATH AROUND POLE"}
, Record {uchar :: Char
uchar = Char
'\10771', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\scpolint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LINE INTEGRATION WITH SEMICIRCULAR PATH AROUND POLE"}
, Record {uchar :: Char
uchar = Char
'\10772', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\npolint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LINE INTEGRATION NOT INCLUDING THE POLE"}
, Record {uchar :: Char
uchar = Char
'\10773', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\pointint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL AROUND A POINT OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10774', commands :: [(Text, Text)]
commands = [(Text
"esint",Text
"\\sqint"),(Text
"wrisym",Text
"\\sqrint"),(Text
"unicode-math",Text
"\\sqint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"QUATERNION INTEGRAL OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10775', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intlarhk")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL WITH LEFTWARDS ARROW WITH HOOK"}
, Record {uchar :: Char
uchar = Char
'\10776', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intx")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL WITH TIMES SIGN"}
, Record {uchar :: Char
uchar = Char
'\10777', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intcap")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL WITH INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\10778', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intcup")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL WITH UNION"}
, Record {uchar :: Char
uchar = Char
'\10779', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\upint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10780', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lowint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"INTEGRAL WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10781', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\Join"),(Text
"unicode-math",Text
"\\Join")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"JOIN"}
, Record {uchar :: Char
uchar = Char
'\10782', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigtriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LARGE LEFT TRIANGLE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10783', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\zcmp"),(Text
"oz",Text
"\\semi"),(Text
"unicode-math",Text
"\\zcmp")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"= \\fatsemi (stmaryrd), Z NOTATION SCHEMA COMPOSITION"}
, Record {uchar :: Char
uchar = Char
'\10784', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\zpipe"),(Text
"unicode-math",Text
"\\zpipe")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"Z NOTATION SCHEMA PIPING"}
, Record {uchar :: Char
uchar = Char
'\10785', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\zproject"),(Text
"oz",Text
"\\project"),(Text
"unicode-math",Text
"\\zproject")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"Z NOTATION SCHEMA PROJECTION"}
, Record {uchar :: Char
uchar = Char
'\10786', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ringplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN WITH SMALL CIRCLE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10787', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\plushat")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN WITH CIRCUMFLEX ACCENT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10788', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN WITH TILDE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10789', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\plusdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN WITH DOT BELOW"}
, Record {uchar :: Char
uchar = Char
'\10790', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\plussim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN WITH TILDE BELOW"}
, Record {uchar :: Char
uchar = Char
'\10791', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\plussubtwo")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN WITH SUBSCRIPT TWO"}
, Record {uchar :: Char
uchar = Char
'\10792', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\plustrif")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN WITH BLACK TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10793', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\commaminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINUS SIGN WITH COMMA ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10794', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\minusdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINUS SIGN WITH DOT BELOW"}
, Record {uchar :: Char
uchar = Char
'\10795', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\minusfdots")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINUS SIGN WITH FALLING DOTS"}
, Record {uchar :: Char
uchar = Char
'\10796', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\minusrdots")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINUS SIGN WITH RISING DOTS"}
, Record {uchar :: Char
uchar = Char
'\10797', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\opluslhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN IN LEFT HALF CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10798', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\oplusrhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN IN RIGHT HALF CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10799', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\times"),(Text
"unicode-math",Text
"\\vectimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"VECTOR OR CROSS PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\10800', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dottimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTIPLICATION SIGN WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10801', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\timesbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTIPLICATION SIGN WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10802', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\btimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SEMIDIRECT PRODUCT WITH BOTTOM CLOSED"}
, Record {uchar :: Char
uchar = Char
'\10803', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smashtimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SMASH PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\10804', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\otimeslhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTIPLICATION SIGN IN LEFT HALF CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10805', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\otimesrhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTIPLICATION SIGN IN RIGHT HALF CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10806', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\otimeshat")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED MULTIPLICATION SIGN WITH CIRCUMFLEX ACCENT"}
, Record {uchar :: Char
uchar = Char
'\10807', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Otimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTIPLICATION SIGN IN DOUBLE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\10808', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\odiv")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CIRCLED DIVISION SIGN"}
, Record {uchar :: Char
uchar = Char
'\10809', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangleplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN IN TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10810', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangleminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MINUS SIGN IN TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10811', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\triangletimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"MULTIPLICATION SIGN IN TRIANGLE"}
, Record {uchar :: Char
uchar = Char
'\10812', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intprod")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERIOR PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\10813', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\intprodr")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"RIGHTHAND INTERIOR PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\10814', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\fcmp"),(Text
"oz",Text
"\\comp"),(Text
"unicode-math",Text
"\\fcmp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"Z NOTATION RELATIONAL COMPOSITION"}
, Record {uchar :: Char
uchar = Char
'\10815', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\amalg"),(Text
"unicode-math",Text
"\\amalg")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"AMALGAMATION OR COPRODUCT"}
, Record {uchar :: Char
uchar = Char
'\10816', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\capdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERSECTION WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10817', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\uminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"UNION WITH MINUS SIGN, z notation bag subtraction"}
, Record {uchar :: Char
uchar = Char
'\10818', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\barcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"UNION WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10819', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\barcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERSECTION WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10820', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\capwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERSECTION WITH LOGICAL AND"}
, Record {uchar :: Char
uchar = Char
'\10821', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cupvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"UNION WITH LOGICAL OR"}
, Record {uchar :: Char
uchar = Char
'\10822', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cupovercap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"UNION ABOVE INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\10823', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\capovercup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERSECTION ABOVE UNION"}
, Record {uchar :: Char
uchar = Char
'\10824', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cupbarcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"UNION ABOVE BAR ABOVE INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\10825', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\capbarcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERSECTION ABOVE BAR ABOVE UNION"}
, Record {uchar :: Char
uchar = Char
'\10826', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twocups")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"UNION BESIDE AND JOINED WITH UNION"}
, Record {uchar :: Char
uchar = Char
'\10827', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twocaps")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"INTERSECTION BESIDE AND JOINED WITH INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\10828', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\closedvarcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CLOSED UNION WITH SERIFS"}
, Record {uchar :: Char
uchar = Char
'\10829', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\closedvarcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CLOSED INTERSECTION WITH SERIFS"}
, Record {uchar :: Char
uchar = Char
'\10830', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Sqcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOUBLE SQUARE INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\10831', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Sqcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOUBLE SQUARE UNION"}
, Record {uchar :: Char
uchar = Char
'\10832', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\closedvarcupsmashprod")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"CLOSED UNION WITH SERIFS AND SMASH PRODUCT"}
, Record {uchar :: Char
uchar = Char
'\10833', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wedgeodot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL AND WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10834', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\veeodot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL OR WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10835', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Wedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOUBLE LOGICAL AND"}
, Record {uchar :: Char
uchar = Char
'\10836', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Vee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOUBLE LOGICAL OR"}
, Record {uchar :: Char
uchar = Char
'\10837', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wedgeonwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TWO INTERSECTING LOGICAL AND"}
, Record {uchar :: Char
uchar = Char
'\10838', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\veeonvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TWO INTERSECTING LOGICAL OR"}
, Record {uchar :: Char
uchar = Char
'\10839', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigslopedvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SLOPING LARGE OR"}
, Record {uchar :: Char
uchar = Char
'\10840', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigslopedwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SLOPING LARGE AND"}
, Record {uchar :: Char
uchar = Char
'\10841', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\veeonwedge")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LOGICAL OR OVERLAPPING LOGICAL AND"}
, Record {uchar :: Char
uchar = Char
'\10842', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wedgemidvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL AND WITH MIDDLE STEM"}
, Record {uchar :: Char
uchar = Char
'\10843', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\veemidvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL OR WITH MIDDLE STEM"}
, Record {uchar :: Char
uchar = Char
'\10844', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\midbarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"ogical and with horizontal dash"}
, Record {uchar :: Char
uchar = Char
'\10845', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\midbarvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL OR WITH HORIZONTAL DASH"}
, Record {uchar :: Char
uchar = Char
'\10846', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\doublebarwedge"),(Text
"unicode-math",Text
"\\doublebarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL AND WITH DOUBLE OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10847', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wedgebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL AND WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10848', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\wedgedoublebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL AND WITH DOUBLE UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10849', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varveebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"SMALL VEE WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10850', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\doublebarvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL OR WITH DOUBLE OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10851', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\veedoublebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"LOGICAL OR WITH DOUBLE UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10852', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\dsub"),(Text
"oz",Text
"\\ndres"),(Text
"unicode-math",Text
"\\dsub")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"Z NOTATION DOMAIN ANTIRESTRICTION"}
, Record {uchar :: Char
uchar = Char
'\10853', commands :: [(Text, Text)]
commands = [(Text
"oz",Text
"\\rsub"),(Text
"oz",Text
"\\nrres"),(Text
"unicode-math",Text
"\\rsub")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"Z NOTATION RANGE ANTIRESTRICTION"}
, Record {uchar :: Char
uchar = Char
'\10854', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN WITH DOT BELOW"}
, Record {uchar :: Char
uchar = Char
'\10855', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dotequiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"IDENTICAL WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10856', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\equivVert")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TRIPLE HORIZONTAL BAR WITH DOUBLE VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10857', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\equivVvert")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TRIPLE HORIZONTAL BAR WITH TRIPLE VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10858', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dotsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TILDE OPERATOR WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10859', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simrdots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TILDE OPERATOR WITH RISING DOTS"}
, Record {uchar :: Char
uchar = Char
'\10860', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simminussim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SIMILAR MINUS SIMILAR"}
, Record {uchar :: Char
uchar = Char
'\10861', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\congdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CONGRUENT WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10862', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\asteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS WITH ASTERISK"}
, Record {uchar :: Char
uchar = Char
'\10863', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hatapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ALMOST EQUAL TO WITH CIRCUMFLEX ACCENT"}
, Record {uchar :: Char
uchar = Char
'\10864', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\approxeqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"APPROXIMATELY EQUAL OR EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10865', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqqplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"EQUALS SIGN ABOVE PLUS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10866', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\pluseqq")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"PLUS SIGN ABOVE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10867', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqqsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN ABOVE TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10868', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Coloneqq"),(Text
"base",Text
"::="),(Text
"unicode-math",Text
"\\Coloneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"x \\Coloneq (txfonts), DOUBLE COLON EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10869', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\Equal"),(Text
"base",Text
"=="),(Text
"unicode-math",Text
"\\eqeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TWO CONSECUTIVE EQUALS SIGNS"}
, Record {uchar :: Char
uchar = Char
'\10870', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\Same"),(Text
"base",Text
"==="),(Text
"unicode-math",Text
"\\eqeqeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"THREE CONSECUTIVE EQUALS SIGNS"}
, Record {uchar :: Char
uchar = Char
'\10871', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ddotseq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN WITH TWO DOTS ABOVE AND TWO DOTS BELOW"}
, Record {uchar :: Char
uchar = Char
'\10872', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\equivDD")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUIVALENT WITH FOUR DOTS ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10873', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ltcir")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN WITH CIRCLE INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10874', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gtcir")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN WITH CIRCLE INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10875', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\ltquest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN WITH QUESTION MARK ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10876', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gtquest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN WITH QUESTION MARK ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10877', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\leqslant"),(Text
"fourier",Text
"\\leqslant"),(Text
"unicode-math",Text
"\\leqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN OR SLANTED EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10878', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\geqslant"),(Text
"fourier",Text
"\\geqslant"),(Text
"unicode-math",Text
"\\geqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN OR SLANTED EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10879', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lesdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN OR SLANTED EQUAL TO WITH DOT INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10880', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gesdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN OR SLANTED EQUAL TO WITH DOT INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10881', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lesdoto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN OR SLANTED EQUAL TO WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10882', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gesdoto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN OR SLANTED EQUAL TO WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10883', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lesdotor")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN OR SLANTED EQUAL TO WITH DOT ABOVE RIGHT"}
, Record {uchar :: Char
uchar = Char
'\10884', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gesdotol")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN OR SLANTED EQUAL TO WITH DOT ABOVE LEFT"}
, Record {uchar :: Char
uchar = Char
'\10885', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lessapprox"),(Text
"unicode-math",Text
"\\lessapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN OR APPROXIMATE"}
, Record {uchar :: Char
uchar = Char
'\10886', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gtrapprox"),(Text
"unicode-math",Text
"\\gtrapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN OR APPROXIMATE"}
, Record {uchar :: Char
uchar = Char
'\10887', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lneq"),(Text
"unicode-math",Text
"\\lneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN AND SINGLE-LINE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10888', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gneq"),(Text
"unicode-math",Text
"\\gneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN AND SINGLE-LINE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10889', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lnapprox"),(Text
"unicode-math",Text
"\\lnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN AND NOT APPROXIMATE"}
, Record {uchar :: Char
uchar = Char
'\10890', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gnapprox"),(Text
"unicode-math",Text
"\\gnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN AND NOT APPROXIMATE"}
, Record {uchar :: Char
uchar = Char
'\10891', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lesseqqgtr"),(Text
"unicode-math",Text
"\\lesseqqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN ABOVE DOUBLE-LINE EQUAL ABOVE GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10892', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\gtreqqless"),(Text
"unicode-math",Text
"\\gtreqqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN ABOVE DOUBLE-LINE EQUAL ABOVE LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10893', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lsime")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN ABOVE SIMILAR OR EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10894', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gsime")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN ABOVE SIMILAR OR EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10895', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lsimg")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN ABOVE SIMILAR ABOVE GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10896', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gsiml")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN ABOVE SIMILAR ABOVE LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10897', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lgE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN ABOVE GREATER-THAN ABOVE DOUBLE-LINE EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10898', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\glE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN ABOVE LESS-THAN ABOVE DOUBLE-LINE EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10899', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lesges")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN ABOVE SLANTED EQUAL ABOVE GREATER-THAN ABOVE SLANTED EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10900', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gesles")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN ABOVE SLANTED EQUAL ABOVE LESS-THAN ABOVE SLANTED EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10901', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\eqslantless"),(Text
"unicode-math",Text
"\\eqslantless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SLANTED EQUAL TO OR LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10902', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\eqslantgtr"),(Text
"unicode-math",Text
"\\eqslantgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SLANTED EQUAL TO OR GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10903', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\elsdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SLANTED EQUAL TO OR LESS-THAN WITH DOT INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10904', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\egsdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SLANTED EQUAL TO OR GREATER-THAN WITH DOT INSIDE"}
, Record {uchar :: Char
uchar = Char
'\10905', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE-LINE EQUAL TO OR LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10906', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE-LINE EQUAL TO OR GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10907', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqqslantless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE-LINE SLANTED EQUAL TO OR LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10908', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\eqqslantgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE-LINE SLANTED EQUAL TO OR GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10909', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SIMILAR OR LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10910', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SIMILAR OR GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10911', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simlE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SIMILAR ABOVE LESS-THAN ABOVE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10912', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\simgE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SIMILAR ABOVE GREATER-THAN ABOVE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10913', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\NestedLessLess"),(Text
"mathabx -amssymb",Text
"\\lll"),(Text
"unicode-math",Text
"\\Lt")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE NESTED LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10914', commands :: [(Text, Text)]
commands = [(Text
"wrisym",Text
"\\NestedGreaterGreater"),(Text
"mathabx -amssymb",Text
"\\ggg"),(Text
"unicode-math",Text
"\\Gt")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE NESTED GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\10915', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\partialmeetcontraction")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"double less-than with underbar"}
, Record {uchar :: Char
uchar = Char
'\10916', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\glj")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN OVERLAPPING LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10917', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gla")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN BESIDE LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\10918', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\leftslice"),(Text
"unicode-math",Text
"\\ltcc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN CLOSED BY CURVE"}
, Record {uchar :: Char
uchar = Char
'\10919', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\rightslice"),(Text
"unicode-math",Text
"\\gtcc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN CLOSED BY CURVE"}
, Record {uchar :: Char
uchar = Char
'\10920', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lescc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LESS-THAN CLOSED BY CURVE ABOVE SLANTED EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10921', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gescc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"GREATER-THAN CLOSED BY CURVE ABOVE SLANTED EQUAL"}
, Record {uchar :: Char
uchar = Char
'\10922', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smt")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SMALLER THAN"}
, Record {uchar :: Char
uchar = Char
'\10923', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lat")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LARGER THAN"}
, Record {uchar :: Char
uchar = Char
'\10924', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smte")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SMALLER THAN OR EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10925', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\late")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LARGER THAN OR EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10926', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bumpeqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN WITH BUMPY ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10927', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\preceq"),(Text
"unicode-math",Text
"\\preceq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PRECEDES ABOVE SINGLE-LINE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10928', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\succeq"),(Text
"unicode-math",Text
"\\succeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS ABOVE SINGLE-LINE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10929', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\precneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PRECEDES ABOVE SINGLE-LINE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10930', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\succneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS ABOVE SINGLE-LINE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10931', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\preceqq"),(Text
"unicode-math",Text
"\\preceqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PRECEDES ABOVE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10932', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\succeqq"),(Text
"unicode-math",Text
"\\succeqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS ABOVE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10933', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\precneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PRECEDES ABOVE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10934', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\succneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS ABOVE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10935', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\precapprox"),(Text
"unicode-math",Text
"\\precapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PRECEDES ABOVE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10936', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\succapprox"),(Text
"unicode-math",Text
"\\succapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS ABOVE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10937', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\precnapprox"),(Text
"unicode-math",Text
"\\precnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PRECEDES ABOVE NOT ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10938', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\succnapprox"),(Text
"unicode-math",Text
"\\succnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUCCEEDS ABOVE NOT ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10939', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\llcurly"),(Text
"unicode-math",Text
"\\Prec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE PRECEDES"}
, Record {uchar :: Char
uchar = Char
'\10940', commands :: [(Text, Text)]
commands = [(Text
"mathabx",Text
"\\ggcurly"),(Text
"unicode-math",Text
"\\Succ")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE SUCCEEDS"}
, Record {uchar :: Char
uchar = Char
'\10941', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subsetdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10942', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supsetdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET WITH DOT"}
, Record {uchar :: Char
uchar = Char
'\10943', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subsetplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET WITH PLUS SIGN BELOW"}
, Record {uchar :: Char
uchar = Char
'\10944', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supsetplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET WITH PLUS SIGN BELOW"}
, Record {uchar :: Char
uchar = Char
'\10945', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\submult")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET WITH MULTIPLICATION SIGN BELOW"}
, Record {uchar :: Char
uchar = Char
'\10946', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supmult")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET WITH MULTIPLICATION SIGN BELOW"}
, Record {uchar :: Char
uchar = Char
'\10947', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subedot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET OF OR EQUAL TO WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10948', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supedot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET OF OR EQUAL TO WITH DOT ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10949', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\subseteqq"),(Text
"unicode-math",Text
"\\subseteqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET OF ABOVE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10950', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\supseteqq"),(Text
"unicode-math",Text
"\\supseteqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET OF ABOVE EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\10951', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET OF ABOVE TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10952', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET OF ABOVE TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10953', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subsetapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET OF ABOVE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10954', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supsetapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET OF ABOVE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10955', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\subsetneqq"),(Text
"unicode-math",Text
"\\subsetneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET OF ABOVE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10956', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\supsetneqq"),(Text
"unicode-math",Text
"\\supsetneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET OF ABOVE NOT EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10957', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lsqhook")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SQUARE LEFT OPEN BOX OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10958', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rsqhook")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SQUARE RIGHT OPEN BOX OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10959', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\csub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CLOSED SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10960', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\csup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CLOSED SUPERSET"}
, Record {uchar :: Char
uchar = Char
'\10961', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\csube")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CLOSED SUBSET OR EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10962', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\csupe")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"CLOSED SUPERSET OR EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\10963', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET ABOVE SUPERSET"}
, Record {uchar :: Char
uchar = Char
'\10964', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET ABOVE SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10965', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\subsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUBSET ABOVE SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10966', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET ABOVE SUPERSET"}
, Record {uchar :: Char
uchar = Char
'\10967', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\suphsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET BESIDE SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10968', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\supdsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SUPERSET BESIDE AND JOINED BY DASH WITH SUBSET"}
, Record {uchar :: Char
uchar = Char
'\10969', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\forkv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"ELEMENT OF OPENING DOWNWARDS"}
, Record {uchar :: Char
uchar = Char
'\10970', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\topfork")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PITCHFORK WITH TEE TOP"}
, Record {uchar :: Char
uchar = Char
'\10971', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mlcp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TRANSVERSAL INTERSECTION"}
, Record {uchar :: Char
uchar = Char
'\10972', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\forks")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"FORKING"}
, Record {uchar :: Char
uchar = Char
'\10973', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\forksnot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"NONFORKING"}
, Record {uchar :: Char
uchar = Char
'\10974', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\shortlefttack")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SHORT LEFT TACK"}
, Record {uchar :: Char
uchar = Char
'\10975', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\shortdowntack")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SHORT DOWN TACK"}
, Record {uchar :: Char
uchar = Char
'\10976', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\shortuptack")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SHORT UP TACK"}
, Record {uchar :: Char
uchar = Char
'\10977', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\perps")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"PERPENDICULAR WITH S"}
, Record {uchar :: Char
uchar = Char
'\10978', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vDdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"VERTICAL BAR TRIPLE RIGHT TURNSTILE"}
, Record {uchar :: Char
uchar = Char
'\10979', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dashV")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE VERTICAL BAR LEFT TURNSTILE"}
, Record {uchar :: Char
uchar = Char
'\10980', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Dashv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"VERTICAL BAR DOUBLE LEFT TURNSTILE"}
, Record {uchar :: Char
uchar = Char
'\10981', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\DashV")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE VERTICAL BAR DOUBLE LEFT TURNSTILE"}
, Record {uchar :: Char
uchar = Char
'\10982', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varVdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG DASH FROM LEFT MEMBER OF DOUBLE VERTICAL"}
, Record {uchar :: Char
uchar = Char
'\10983', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Barv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SHORT DOWN TACK WITH OVERBAR"}
, Record {uchar :: Char
uchar = Char
'\10984', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vBar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SHORT UP TACK WITH UNDERBAR"}
, Record {uchar :: Char
uchar = Char
'\10985', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vBarv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"SHORT UP TACK ABOVE SHORT DOWN TACK"}
, Record {uchar :: Char
uchar = Char
'\10986', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Top"),(Text
"unicode-math",Text
"\\barV")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE DOWN TACK"}
, Record {uchar :: Char
uchar = Char
'\10987', commands :: [(Text, Text)]
commands = [(Text
"txfonts",Text
"\\Bot"),(Text
"txfonts",Text
"\\Perp"),(Text
"unicode-math",Text
"\\Vbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE UP TACK"}
, Record {uchar :: Char
uchar = Char
'\10988', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Not")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE STROKE NOT SIGN"}
, Record {uchar :: Char
uchar = Char
'\10989', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bNot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"REVERSED DOUBLE STROKE NOT SIGN"}
, Record {uchar :: Char
uchar = Char
'\10990', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\revnmid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOES NOT DIVIDE WITH REVERSED NEGATION SLASH"}
, Record {uchar :: Char
uchar = Char
'\10991', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\cirmid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"VERTICAL LINE WITH CIRCLE ABOVE"}
, Record {uchar :: Char
uchar = Char
'\10992', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\midcir")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"VERTICAL LINE WITH CIRCLE BELOW"}
, Record {uchar :: Char
uchar = Char
'\10993', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\topcir")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWN TACK WITH CIRCLE BELOW"}
, Record {uchar :: Char
uchar = Char
'\10994', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nhpar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PARALLEL WITH HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10995', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\parsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"PARALLEL WITH TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10996', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\interleave"),(Text
"unicode-math",Text
"\\interleave")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TRIPLE VERTICAL BAR BINARY RELATION"}
, Record {uchar :: Char
uchar = Char
'\10997', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nhVvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TRIPLE VERTICAL BAR WITH HORIZONTAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\10998', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\threedotcolon")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TRIPLE COLON OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\10999', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lllnest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TRIPLE NESTED LESS-THAN"}
, Record {uchar :: Char
uchar = Char
'\11000', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\gggnest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TRIPLE NESTED GREATER-THAN"}
, Record {uchar :: Char
uchar = Char
'\11001', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leqqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE-LINE SLANTED LESS-THAN OR EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\11002', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\geqqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"DOUBLE-LINE SLANTED GREATER-THAN OR EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\11003', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\trslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"TRIPLE SOLIDUS BINARY RELATION"}
, Record {uchar :: Char
uchar = Char
'\11004', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\biginterleave"),(Text
"unicode-math",Text
"\\biginterleave")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"LARGE TRIPLE VERTICAL BAR OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\11005', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\sslash"),(Text
"txfonts",Text
"\\varparallel"),(Text
"unicode-math",Text
"\\sslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"DOUBLE SOLIDUS OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\11006', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\talloblong"),(Text
"unicode-math",Text
"\\talloblong")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = Text
"WHITE VERTICAL BAR"}
, Record {uchar :: Char
uchar = Char
'\11007', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bigtalloblong")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = Text
"N-ARY WHITE VERTICAL BAR"}
, Record {uchar :: Char
uchar = Char
'\11008', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH EAST WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11009', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH WEST WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11010', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SOUTH EAST WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11011', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SOUTH WEST WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11012', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT RIGHT WHITE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11013', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFTWARDS BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11014', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UPWARDS BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11015', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOWNWARDS BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11016', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH EAST BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11017', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"NORTH WEST BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11018', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SOUTH EAST BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11019', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SOUTH WEST BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11020', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFT RIGHT BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11021', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"UP DOWN BLACK ARROW"}
, Record {uchar :: Char
uchar = Char
'\11022', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH TIP DOWNWARDS"}
, Record {uchar :: Char
uchar = Char
'\11023', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"RIGHTWARDS ARROW WITH TIP UPWARDS"}
, Record {uchar :: Char
uchar = Char
'\11024', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH TIP DOWNWARDS"}
, Record {uchar :: Char
uchar = Char
'\11025', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH TIP UPWARDS"}
, Record {uchar :: Char
uchar = Char
'\11026', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squaretopblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE WITH TOP HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11027', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarebotblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE WITH BOTTOM HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11028', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squareurblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE WITH UPPER RIGHT DIAGONAL HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11029', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\squarellblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SQUARE WITH LOWER LEFT DIAGONAL HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11030', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diamondleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIAMOND WITH LEFT HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11031', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diamondrightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIAMOND WITH RIGHT HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11032', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diamondtopblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIAMOND WITH TOP HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11033', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\diamondbotblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DIAMOND WITH BOTTOM HALF BLACK"}
, Record {uchar :: Char
uchar = Char
'\11034', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\dottedsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"DOTTED SQUARE"}
, Record {uchar :: Char
uchar = Char
'\11035', commands :: [(Text, Text)]
commands = [(Text
"fourier",Text
"\\blacksquare"),(Text
"unicode-math",Text
"\\lgblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK LARGE SQUARE"}
, Record {uchar :: Char
uchar = Char
'\11036', commands :: [(Text, Text)]
commands = [(Text
"fourier",Text
"\\square"),(Text
"unicode-math",Text
"\\lgwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE LARGE SQUARE"}
, Record {uchar :: Char
uchar = Char
'\11037', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\centerdot"),(Text
"unicode-math",Text
"\\vysmblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"t \\Squaredot (marvosym), BLACK VERY SMALL SQUARE"}
, Record {uchar :: Char
uchar = Char
'\11038', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\vysmwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE VERY SMALL SQUARE"}
, Record {uchar :: Char
uchar = Char
'\11039', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\pentagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK PENTAGON"}
, Record {uchar :: Char
uchar = Char
'\11040', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\pentagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE PENTAGON"}
, Record {uchar :: Char
uchar = Char
'\11041', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varhexagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE HEXAGON"}
, Record {uchar :: Char
uchar = Char
'\11042', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\varhexagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK HEXAGON"}
, Record {uchar :: Char
uchar = Char
'\11043', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hexagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HORIZONTAL BLACK HEXAGON"}
, Record {uchar :: Char
uchar = Char
'\11044', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lgblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK LARGE CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\11045', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mdblkdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK MEDIUM DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\11046', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mdwhtdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE MEDIUM DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\11047', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\blacklozenge"),(Text
"unicode-math",Text
"\\mdblklozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK MEDIUM LOZENGE"}
, Record {uchar :: Char
uchar = Char
'\11048', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\lozenge"),(Text
"unicode-math",Text
"\\mdwhtlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE MEDIUM LOZENGE"}
, Record {uchar :: Char
uchar = Char
'\11049', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smblkdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK SMALL DIAMOND"}
, Record {uchar :: Char
uchar = Char
'\11050', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smblklozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK SMALL LOZENGE"}
, Record {uchar :: Char
uchar = Char
'\11051', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smwhtlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SMALL LOZENGE"}
, Record {uchar :: Char
uchar = Char
'\11052', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blkhorzoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK HORIZONTAL ELLIPSE"}
, Record {uchar :: Char
uchar = Char
'\11053', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\whthorzoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE HORIZONTAL ELLIPSE"}
, Record {uchar :: Char
uchar = Char
'\11054', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\blkvertoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK VERTICAL ELLIPSE"}
, Record {uchar :: Char
uchar = Char
'\11055', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\whtvertoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE VERTICAL ELLIPSE"}
, Record {uchar :: Char
uchar = Char
'\11056', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\circleonleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT ARROW WITH SMALL CIRCLE"}
, Record {uchar :: Char
uchar = Char
'\11057', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftthreearrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"THREE LEFTWARDS ARROWS"}
, Record {uchar :: Char
uchar = Char
'\11058', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowonoplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFT ARROW WITH CIRCLED PLUS"}
, Record {uchar :: Char
uchar = Char
'\11059', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\longleftsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LONG LEFTWARDS SQUIGGLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11060', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvtwoheadleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS TWO-HEADED ARROW WITH VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\11061', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nVtwoheadleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS TWO-HEADED ARROW WITH DOUBLE VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\11062', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twoheadmapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS TWO-HEADED ARROW FROM BAR"}
, Record {uchar :: Char
uchar = Char
'\11063', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twoheadleftdbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"leftwards two-headed triple-dash arrow"}
, Record {uchar :: Char
uchar = Char
'\11064', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftdotarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH DOTTED STEM"}
, Record {uchar :: Char
uchar = Char
'\11065', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH TAIL WITH VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\11066', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nVleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\11067', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\twoheadleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS TWO-HEADED ARROW WITH TAIL"}
, Record {uchar :: Char
uchar = Char
'\11068', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nvtwoheadleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS TWO-HEADED ARROW WITH TAIL WITH VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\11069', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\nVtwoheadleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS TWO-HEADED ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE"}
, Record {uchar :: Char
uchar = Char
'\11070', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowx")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW THROUGH X"}
, Record {uchar :: Char
uchar = Char
'\11071', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftcurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"WAVE ARROW POINTING DIRECTLY LEFT"}
, Record {uchar :: Char
uchar = Char
'\11072', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\equalleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"EQUALS SIGN ABOVE LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\11073', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bsimilarleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"REVERSE TILDE OPERATOR ABOVE LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\11074', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowbackapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW ABOVE REVERSE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\11075', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"rightwards arrow through less-than"}
, Record {uchar :: Char
uchar = Char
'\11076', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowsupset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"rightwards arrow through subset"}
, Record {uchar :: Char
uchar = Char
'\11077', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\LLeftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS QUADRUPLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11078', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\RRightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS QUADRUPLE ARROW"}
, Record {uchar :: Char
uchar = Char
'\11079', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\bsimilarrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"REVERSE TILDE OPERATOR ABOVE RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\11080', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowbackapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"RIGHTWARDS ARROW ABOVE REVERSE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\11081', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\similarleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"TILDE OPERATOR ABOVE LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\11082', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW ABOVE ALMOST EQUAL TO"}
, Record {uchar :: Char
uchar = Char
'\11083', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\leftarrowbsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"LEFTWARDS ARROW ABOVE REVERSE TILDE OPERATOR"}
, Record {uchar :: Char
uchar = Char
'\11084', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightarrowbsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = Text
"righttwards arrow above reverse tilde operator"}
, Record {uchar :: Char
uchar = Char
'\11088', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\medwhitestar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE MEDIUM STAR"}
, Record {uchar :: Char
uchar = Char
'\11089', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\medblackstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"black medium star"}
, Record {uchar :: Char
uchar = Char
'\11090', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\smwhitestar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE SMALL STAR"}
, Record {uchar :: Char
uchar = Char
'\11091', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightpentagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"BLACK RIGHT-POINTING PENTAGON"}
, Record {uchar :: Char
uchar = Char
'\11092', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rightpentagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"WHITE RIGHT-POINTING PENTAGON"}
, Record {uchar :: Char
uchar = Char
'\12296', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\langle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT ANGLE BRACKET (deprecated for math use)"}
, Record {uchar :: Char
uchar = Char
'\12297', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT ANGLE BRACKET (deprecated for math use)"}
, Record {uchar :: Char
uchar = Char
'\12306', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\postalmark")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"POSTAL MARK"}
, Record {uchar :: Char
uchar = Char
'\12308', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"left broken bracket"}
, Record {uchar :: Char
uchar = Char
'\12309', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"right broken bracket"}
, Record {uchar :: Char
uchar = Char
'\12312', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT WHITE TORTOISE SHELL BRACKET"}
, Record {uchar :: Char
uchar = Char
'\12313', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\Rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT WHITE TORTOISE SHELL BRACKET"}
, Record {uchar :: Char
uchar = Char
'\12314', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\llbracket")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = Text
"LEFT WHITE SQUARE BRACKET (deprecated for math use)"}
, Record {uchar :: Char
uchar = Char
'\12315', commands :: [(Text, Text)]
commands = [(Text
"stmaryrd",Text
"\\rrbracket")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = Text
"RIGHT WHITE SQUARE BRACKET (deprecated for math use)"}
, Record {uchar :: Char
uchar = Char
'\12336', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\hzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"zigzag"}
, Record {uchar :: Char
uchar = Char
'\12398', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"HIRAGANA LETTER NO"}
, Record {uchar :: Char
uchar = Char
'\64297', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HEBREW LETTER ALTERNATIVE PLUS SIGN (doesn't have cross shape)"}
, Record {uchar :: Char
uchar = Char
'\65024', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = Text
"VARIATION SELECTOR-1"}
, Record {uchar :: Char
uchar = Char
'\65121', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SMALL ASTERISK"}
, Record {uchar :: Char
uchar = Char
'\65122', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SMALL PLUS SIGN"}
, Record {uchar :: Char
uchar = Char
'\65123', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SMALL HYPHEN-MINUS"}
, Record {uchar :: Char
uchar = Char
'\65124', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SMALL LESS-THAN SIGN"}
, Record {uchar :: Char
uchar = Char
'\65125', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SMALL GREATER-THAN SIGN"}
, Record {uchar :: Char
uchar = Char
'\65126', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SMALL EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\65128', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"SMALL REVERSE SOLIDUS"}
, Record {uchar :: Char
uchar = Char
'\65291', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH PLUS SIGN"}
, Record {uchar :: Char
uchar = Char
'\65308', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH LESS-THAN SIGN"}
, Record {uchar :: Char
uchar = Char
'\65309', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH EQUALS SIGN"}
, Record {uchar :: Char
uchar = Char
'\65310', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH GREATER-THAN SIGN"}
, Record {uchar :: Char
uchar = Char
'\65340', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH REVERSE SOLIDUS"}
, Record {uchar :: Char
uchar = Char
'\65342', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH CIRCUMFLEX ACCENT"}
, Record {uchar :: Char
uchar = Char
'\65372', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH VERTICAL LINE"}
, Record {uchar :: Char
uchar = Char
'\65374', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH TILDE"}
, Record {uchar :: Char
uchar = Char
'\65506', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"FULLWIDTH NOT SIGN"}
, Record {uchar :: Char
uchar = Char
'\65513', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HALFWIDTH LEFTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\65514', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HALFWIDTH UPWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\65515', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HALFWIDTH RIGHTWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\65516', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"HALFWIDTH DOWNWARDS ARROW"}
, Record {uchar :: Char
uchar = Char
'\119808', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{A}"),(Text
"unicode-math",Text
"\\mbfA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\119809', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{B}"),(Text
"unicode-math",Text
"\\mbfB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\119810', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{C}"),(Text
"unicode-math",Text
"\\mbfC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\119811', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{D}"),(Text
"unicode-math",Text
"\\mbfD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\119812', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{E}"),(Text
"unicode-math",Text
"\\mbfE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\119813', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{F}"),(Text
"unicode-math",Text
"\\mbfF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\119814', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{G}"),(Text
"unicode-math",Text
"\\mbfG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\119815', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{H}"),(Text
"unicode-math",Text
"\\mbfH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\119816', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{I}"),(Text
"unicode-math",Text
"\\mbfI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\119817', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{J}"),(Text
"unicode-math",Text
"\\mbfJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\119818', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{K}"),(Text
"unicode-math",Text
"\\mbfK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\119819', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{L}"),(Text
"unicode-math",Text
"\\mbfL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\119820', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{M}"),(Text
"unicode-math",Text
"\\mbfM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\119821', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{N}"),(Text
"unicode-math",Text
"\\mbfN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\119822', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{O}"),(Text
"unicode-math",Text
"\\mbfO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\119823', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{P}"),(Text
"unicode-math",Text
"\\mbfP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\119824', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{Q}"),(Text
"unicode-math",Text
"\\mbfQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\119825', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{R}"),(Text
"unicode-math",Text
"\\mbfR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\119826', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{S}"),(Text
"unicode-math",Text
"\\mbfS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\119827', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{T}"),(Text
"unicode-math",Text
"\\mbfT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\119828', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{U}"),(Text
"unicode-math",Text
"\\mbfU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\119829', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{V}"),(Text
"unicode-math",Text
"\\mbfV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\119830', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{W}"),(Text
"unicode-math",Text
"\\mbfW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\119831', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{X}"),(Text
"unicode-math",Text
"\\mbfX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\119832', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{Y}"),(Text
"unicode-math",Text
"\\mbfY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\119833', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{Z}"),(Text
"unicode-math",Text
"\\mbfZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\119834', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{a}"),(Text
"unicode-math",Text
"\\mbfa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL A"}
, Record {uchar :: Char
uchar = Char
'\119835', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{b}"),(Text
"unicode-math",Text
"\\mbfb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL B"}
, Record {uchar :: Char
uchar = Char
'\119836', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{c}"),(Text
"unicode-math",Text
"\\mbfc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL C"}
, Record {uchar :: Char
uchar = Char
'\119837', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{d}"),(Text
"unicode-math",Text
"\\mbfd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL D"}
, Record {uchar :: Char
uchar = Char
'\119838', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{e}"),(Text
"unicode-math",Text
"\\mbfe")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL E"}
, Record {uchar :: Char
uchar = Char
'\119839', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{f}"),(Text
"unicode-math",Text
"\\mbff")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL F"}
, Record {uchar :: Char
uchar = Char
'\119840', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{g}"),(Text
"unicode-math",Text
"\\mbfg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL G"}
, Record {uchar :: Char
uchar = Char
'\119841', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{h}"),(Text
"unicode-math",Text
"\\mbfh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL H"}
, Record {uchar :: Char
uchar = Char
'\119842', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{i}"),(Text
"unicode-math",Text
"\\mbfi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL I"}
, Record {uchar :: Char
uchar = Char
'\119843', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{j}"),(Text
"unicode-math",Text
"\\mbfj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL J"}
, Record {uchar :: Char
uchar = Char
'\119844', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{k}"),(Text
"unicode-math",Text
"\\mbfk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL K"}
, Record {uchar :: Char
uchar = Char
'\119845', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{l}"),(Text
"unicode-math",Text
"\\mbfl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL L"}
, Record {uchar :: Char
uchar = Char
'\119846', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{m}"),(Text
"unicode-math",Text
"\\mbfm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL M"}
, Record {uchar :: Char
uchar = Char
'\119847', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{n}"),(Text
"unicode-math",Text
"\\mbfn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL N"}
, Record {uchar :: Char
uchar = Char
'\119848', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{o}"),(Text
"unicode-math",Text
"\\mbfo")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL O"}
, Record {uchar :: Char
uchar = Char
'\119849', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{p}"),(Text
"unicode-math",Text
"\\mbfp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL P"}
, Record {uchar :: Char
uchar = Char
'\119850', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{q}"),(Text
"unicode-math",Text
"\\mbfq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\119851', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{r}"),(Text
"unicode-math",Text
"\\mbfr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL R"}
, Record {uchar :: Char
uchar = Char
'\119852', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{s}"),(Text
"unicode-math",Text
"\\mbfs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL S"}
, Record {uchar :: Char
uchar = Char
'\119853', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{t}"),(Text
"unicode-math",Text
"\\mbft")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL T"}
, Record {uchar :: Char
uchar = Char
'\119854', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{u}"),(Text
"unicode-math",Text
"\\mbfu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL U"}
, Record {uchar :: Char
uchar = Char
'\119855', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{v}"),(Text
"unicode-math",Text
"\\mbfv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL V"}
, Record {uchar :: Char
uchar = Char
'\119856', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{w}"),(Text
"unicode-math",Text
"\\mbfw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL W"}
, Record {uchar :: Char
uchar = Char
'\119857', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{x}"),(Text
"unicode-math",Text
"\\mbfx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL X"}
, Record {uchar :: Char
uchar = Char
'\119858', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{y}"),(Text
"unicode-math",Text
"\\mbfy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\119859', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{z}"),(Text
"unicode-math",Text
"\\mbfz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\119860', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"A"),(Text
"base",Text
"\\mathit{A}"),(Text
"unicode-math",Text
"\\mitA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\119861', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"B"),(Text
"base",Text
"\\mathit{B}"),(Text
"unicode-math",Text
"\\mitB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\119862', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"C"),(Text
"base",Text
"\\mathit{C}"),(Text
"unicode-math",Text
"\\mitC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\119863', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"D"),(Text
"base",Text
"\\mathit{D}"),(Text
"unicode-math",Text
"\\mitD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\119864', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"E"),(Text
"base",Text
"\\mathit{E}"),(Text
"unicode-math",Text
"\\mitE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\119865', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"F"),(Text
"base",Text
"\\mathit{F}"),(Text
"unicode-math",Text
"\\mitF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\119866', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"G"),(Text
"base",Text
"\\mathit{G}"),(Text
"unicode-math",Text
"\\mitG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\119867', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"H"),(Text
"base",Text
"\\mathit{H}"),(Text
"unicode-math",Text
"\\mitH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\119868', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"I"),(Text
"base",Text
"\\mathit{I}"),(Text
"unicode-math",Text
"\\mitI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\119869', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"J"),(Text
"base",Text
"\\mathit{J}"),(Text
"unicode-math",Text
"\\mitJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\119870', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"K"),(Text
"base",Text
"\\mathit{K}"),(Text
"unicode-math",Text
"\\mitK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\119871', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"L"),(Text
"base",Text
"\\mathit{L}"),(Text
"unicode-math",Text
"\\mitL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\119872', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"M"),(Text
"base",Text
"\\mathit{M}"),(Text
"unicode-math",Text
"\\mitM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\119873', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"N"),(Text
"base",Text
"\\mathit{N}"),(Text
"unicode-math",Text
"\\mitN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\119874', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"O"),(Text
"base",Text
"\\mathit{O}"),(Text
"unicode-math",Text
"\\mitO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\119875', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"P"),(Text
"base",Text
"\\mathit{P}"),(Text
"unicode-math",Text
"\\mitP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\119876', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"Q"),(Text
"base",Text
"\\mathit{Q}"),(Text
"unicode-math",Text
"\\mitQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\119877', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"R"),(Text
"base",Text
"\\mathit{R}"),(Text
"unicode-math",Text
"\\mitR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\119878', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"S"),(Text
"base",Text
"\\mathit{S}"),(Text
"unicode-math",Text
"\\mitS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\119879', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"T"),(Text
"base",Text
"\\mathit{T}"),(Text
"unicode-math",Text
"\\mitT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\119880', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"U"),(Text
"base",Text
"\\mathit{U}"),(Text
"unicode-math",Text
"\\mitU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\119881', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"V"),(Text
"base",Text
"\\mathit{V}"),(Text
"unicode-math",Text
"\\mitV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\119882', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"W"),(Text
"base",Text
"\\mathit{W}"),(Text
"unicode-math",Text
"\\mitW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\119883', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"X"),(Text
"base",Text
"\\mathit{X}"),(Text
"unicode-math",Text
"\\mitX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\119884', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"Y"),(Text
"base",Text
"\\mathit{Y}"),(Text
"unicode-math",Text
"\\mitY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\119885', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"Z"),(Text
"base",Text
"\\mathit{Z}"),(Text
"unicode-math",Text
"\\mitZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\119886', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"a"),(Text
"base",Text
"\\mathit{a}"),(Text
"unicode-math",Text
"\\mita")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL A"}
, Record {uchar :: Char
uchar = Char
'\119887', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"b"),(Text
"base",Text
"\\mathit{b}"),(Text
"unicode-math",Text
"\\mitb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL B"}
, Record {uchar :: Char
uchar = Char
'\119888', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"c"),(Text
"base",Text
"\\mathit{c}"),(Text
"unicode-math",Text
"\\mitc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL C"}
, Record {uchar :: Char
uchar = Char
'\119889', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"d"),(Text
"base",Text
"\\mathit{d}"),(Text
"unicode-math",Text
"\\mitd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL D"}
, Record {uchar :: Char
uchar = Char
'\119890', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"e"),(Text
"base",Text
"\\mathit{e}"),(Text
"unicode-math",Text
"\\mite")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL E"}
, Record {uchar :: Char
uchar = Char
'\119891', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"f"),(Text
"base",Text
"\\mathit{f}"),(Text
"unicode-math",Text
"\\mitf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL F"}
, Record {uchar :: Char
uchar = Char
'\119892', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"g"),(Text
"base",Text
"\\mathit{g}"),(Text
"unicode-math",Text
"\\mitg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL G"}
, Record {uchar :: Char
uchar = Char
'\119894', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"i"),(Text
"base",Text
"\\mathit{i}"),(Text
"unicode-math",Text
"\\miti")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL I"}
, Record {uchar :: Char
uchar = Char
'\119895', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"j"),(Text
"base",Text
"\\mathit{j}"),(Text
"unicode-math",Text
"\\mitj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL J"}
, Record {uchar :: Char
uchar = Char
'\119896', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"k"),(Text
"base",Text
"\\mathit{k}"),(Text
"unicode-math",Text
"\\mitk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL K"}
, Record {uchar :: Char
uchar = Char
'\119897', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"l"),(Text
"base",Text
"\\mathit{l}"),(Text
"unicode-math",Text
"\\mitl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL L"}
, Record {uchar :: Char
uchar = Char
'\119898', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"m"),(Text
"base",Text
"\\mathit{m}"),(Text
"unicode-math",Text
"\\mitm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL M"}
, Record {uchar :: Char
uchar = Char
'\119899', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"n"),(Text
"base",Text
"\\mathit{n}"),(Text
"unicode-math",Text
"\\mitn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL N"}
, Record {uchar :: Char
uchar = Char
'\119900', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"o"),(Text
"base",Text
"\\mathit{o}"),(Text
"unicode-math",Text
"\\mito")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL O"}
, Record {uchar :: Char
uchar = Char
'\119901', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"p"),(Text
"base",Text
"\\mathit{p}"),(Text
"unicode-math",Text
"\\mitp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL P"}
, Record {uchar :: Char
uchar = Char
'\119902', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"q"),(Text
"base",Text
"\\mathit{q}"),(Text
"unicode-math",Text
"\\mitq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\119903', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"r"),(Text
"base",Text
"\\mathit{r}"),(Text
"unicode-math",Text
"\\mitr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL R"}
, Record {uchar :: Char
uchar = Char
'\119904', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"s"),(Text
"base",Text
"\\mathit{s}"),(Text
"unicode-math",Text
"\\mits")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL S"}
, Record {uchar :: Char
uchar = Char
'\119905', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"t"),(Text
"base",Text
"\\mathit{t}"),(Text
"unicode-math",Text
"\\mitt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL T"}
, Record {uchar :: Char
uchar = Char
'\119906', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"u"),(Text
"base",Text
"\\mathit{u}"),(Text
"unicode-math",Text
"\\mitu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL U"}
, Record {uchar :: Char
uchar = Char
'\119907', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"v"),(Text
"base",Text
"\\mathit{v}"),(Text
"unicode-math",Text
"\\mitv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL V"}
, Record {uchar :: Char
uchar = Char
'\119908', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"w"),(Text
"base",Text
"\\mathit{w}"),(Text
"unicode-math",Text
"\\mitw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL W"}
, Record {uchar :: Char
uchar = Char
'\119909', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"x"),(Text
"base",Text
"\\mathit{x}"),(Text
"unicode-math",Text
"\\mitx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL X"}
, Record {uchar :: Char
uchar = Char
'\119910', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"y"),(Text
"base",Text
"\\mathit{y}"),(Text
"unicode-math",Text
"\\mity")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\119911', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"z"),(Text
"base",Text
"\\mathit{z}"),(Text
"unicode-math",Text
"\\mitz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\119912', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{A}"),(Text
"fixmath",Text
"\\mathbold{A}"),(Text
"unicode-math",Text
"\\mbfitA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\119913', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{B}"),(Text
"fixmath",Text
"\\mathbold{B}"),(Text
"unicode-math",Text
"\\mbfitB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\119914', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{C}"),(Text
"fixmath",Text
"\\mathbold{C}"),(Text
"unicode-math",Text
"\\mbfitC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\119915', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{D}"),(Text
"fixmath",Text
"\\mathbold{D}"),(Text
"unicode-math",Text
"\\mbfitD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\119916', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{E}"),(Text
"fixmath",Text
"\\mathbold{E}"),(Text
"unicode-math",Text
"\\mbfitE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\119917', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{F}"),(Text
"fixmath",Text
"\\mathbold{F}"),(Text
"unicode-math",Text
"\\mbfitF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\119918', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{G}"),(Text
"fixmath",Text
"\\mathbold{G}"),(Text
"unicode-math",Text
"\\mbfitG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\119919', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{H}"),(Text
"fixmath",Text
"\\mathbold{H}"),(Text
"unicode-math",Text
"\\mbfitH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\119920', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{I}"),(Text
"fixmath",Text
"\\mathbold{I}"),(Text
"unicode-math",Text
"\\mbfitI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\119921', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{J}"),(Text
"fixmath",Text
"\\mathbold{J}"),(Text
"unicode-math",Text
"\\mbfitJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\119922', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{K}"),(Text
"fixmath",Text
"\\mathbold{K}"),(Text
"unicode-math",Text
"\\mbfitK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\119923', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{L}"),(Text
"fixmath",Text
"\\mathbold{L}"),(Text
"unicode-math",Text
"\\mbfitL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\119924', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{M}"),(Text
"fixmath",Text
"\\mathbold{M}"),(Text
"unicode-math",Text
"\\mbfitM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\119925', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{N}"),(Text
"fixmath",Text
"\\mathbold{N}"),(Text
"unicode-math",Text
"\\mbfitN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\119926', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{O}"),(Text
"fixmath",Text
"\\mathbold{O}"),(Text
"unicode-math",Text
"\\mbfitO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\119927', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{P}"),(Text
"fixmath",Text
"\\mathbold{P}"),(Text
"unicode-math",Text
"\\mbfitP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\119928', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{Q}"),(Text
"fixmath",Text
"\\mathbold{Q}"),(Text
"unicode-math",Text
"\\mbfitQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\119929', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{R}"),(Text
"fixmath",Text
"\\mathbold{R}"),(Text
"unicode-math",Text
"\\mbfitR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\119930', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{S}"),(Text
"fixmath",Text
"\\mathbold{S}"),(Text
"unicode-math",Text
"\\mbfitS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\119931', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{T}"),(Text
"fixmath",Text
"\\mathbold{T}"),(Text
"unicode-math",Text
"\\mbfitT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\119932', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{U}"),(Text
"fixmath",Text
"\\mathbold{U}"),(Text
"unicode-math",Text
"\\mbfitU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\119933', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{V}"),(Text
"fixmath",Text
"\\mathbold{V}"),(Text
"unicode-math",Text
"\\mbfitV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\119934', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{W}"),(Text
"fixmath",Text
"\\mathbold{W}"),(Text
"unicode-math",Text
"\\mbfitW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\119935', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{X}"),(Text
"fixmath",Text
"\\mathbold{X}"),(Text
"unicode-math",Text
"\\mbfitX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\119936', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{Y}"),(Text
"fixmath",Text
"\\mathbold{Y}"),(Text
"unicode-math",Text
"\\mbfitY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\119937', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{Z}"),(Text
"fixmath",Text
"\\mathbold{Z}"),(Text
"unicode-math",Text
"\\mbfitZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\119938', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{a}"),(Text
"fixmath",Text
"\\mathbold{a}"),(Text
"unicode-math",Text
"\\mbfita")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL A"}
, Record {uchar :: Char
uchar = Char
'\119939', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{b}"),(Text
"fixmath",Text
"\\mathbold{b}"),(Text
"unicode-math",Text
"\\mbfitb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL B"}
, Record {uchar :: Char
uchar = Char
'\119940', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{c}"),(Text
"fixmath",Text
"\\mathbold{c}"),(Text
"unicode-math",Text
"\\mbfitc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL C"}
, Record {uchar :: Char
uchar = Char
'\119941', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{d}"),(Text
"fixmath",Text
"\\mathbold{d}"),(Text
"unicode-math",Text
"\\mbfitd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL D"}
, Record {uchar :: Char
uchar = Char
'\119942', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{e}"),(Text
"fixmath",Text
"\\mathbold{e}"),(Text
"unicode-math",Text
"\\mbfite")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL E"}
, Record {uchar :: Char
uchar = Char
'\119943', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{f}"),(Text
"fixmath",Text
"\\mathbold{f}"),(Text
"unicode-math",Text
"\\mbfitf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL F"}
, Record {uchar :: Char
uchar = Char
'\119944', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{g}"),(Text
"fixmath",Text
"\\mathbold{g}"),(Text
"unicode-math",Text
"\\mbfitg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL G"}
, Record {uchar :: Char
uchar = Char
'\119945', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{h}"),(Text
"fixmath",Text
"\\mathbold{h}"),(Text
"unicode-math",Text
"\\mbfith")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL H"}
, Record {uchar :: Char
uchar = Char
'\119946', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{i}"),(Text
"fixmath",Text
"\\mathbold{i}"),(Text
"unicode-math",Text
"\\mbfiti")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL I"}
, Record {uchar :: Char
uchar = Char
'\119947', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{j}"),(Text
"fixmath",Text
"\\mathbold{j}"),(Text
"unicode-math",Text
"\\mbfitj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL J"}
, Record {uchar :: Char
uchar = Char
'\119948', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{k}"),(Text
"fixmath",Text
"\\mathbold{k}"),(Text
"unicode-math",Text
"\\mbfitk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL K"}
, Record {uchar :: Char
uchar = Char
'\119949', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{l}"),(Text
"fixmath",Text
"\\mathbold{l}"),(Text
"unicode-math",Text
"\\mbfitl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL L"}
, Record {uchar :: Char
uchar = Char
'\119950', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{m}"),(Text
"fixmath",Text
"\\mathbold{m}"),(Text
"unicode-math",Text
"\\mbfitm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL M"}
, Record {uchar :: Char
uchar = Char
'\119951', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{n}"),(Text
"fixmath",Text
"\\mathbold{n}"),(Text
"unicode-math",Text
"\\mbfitn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL N"}
, Record {uchar :: Char
uchar = Char
'\119952', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{o}"),(Text
"fixmath",Text
"\\mathbold{o}"),(Text
"unicode-math",Text
"\\mbfito")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL O"}
, Record {uchar :: Char
uchar = Char
'\119953', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{p}"),(Text
"fixmath",Text
"\\mathbold{p}"),(Text
"unicode-math",Text
"\\mbfitp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL P"}
, Record {uchar :: Char
uchar = Char
'\119954', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{q}"),(Text
"fixmath",Text
"\\mathbold{q}"),(Text
"unicode-math",Text
"\\mbfitq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\119955', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{r}"),(Text
"fixmath",Text
"\\mathbold{r}"),(Text
"unicode-math",Text
"\\mbfitr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL R"}
, Record {uchar :: Char
uchar = Char
'\119956', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{s}"),(Text
"fixmath",Text
"\\mathbold{s}"),(Text
"unicode-math",Text
"\\mbfits")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL S"}
, Record {uchar :: Char
uchar = Char
'\119957', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{t}"),(Text
"fixmath",Text
"\\mathbold{t}"),(Text
"unicode-math",Text
"\\mbfitt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL T"}
, Record {uchar :: Char
uchar = Char
'\119958', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{u}"),(Text
"fixmath",Text
"\\mathbold{u}"),(Text
"unicode-math",Text
"\\mbfitu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL U"}
, Record {uchar :: Char
uchar = Char
'\119959', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{v}"),(Text
"fixmath",Text
"\\mathbold{v}"),(Text
"unicode-math",Text
"\\mbfitv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL V"}
, Record {uchar :: Char
uchar = Char
'\119960', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{w}"),(Text
"fixmath",Text
"\\mathbold{w}"),(Text
"unicode-math",Text
"\\mbfitw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL W"}
, Record {uchar :: Char
uchar = Char
'\119961', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{x}"),(Text
"fixmath",Text
"\\mathbold{x}"),(Text
"unicode-math",Text
"\\mbfitx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL X"}
, Record {uchar :: Char
uchar = Char
'\119962', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{y}"),(Text
"fixmath",Text
"\\mathbold{y}"),(Text
"unicode-math",Text
"\\mbfity")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\119963', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{z}"),(Text
"fixmath",Text
"\\mathbold{z}"),(Text
"unicode-math",Text
"\\mbfitz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\119964', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{A}"),(Text
"unicode-math",Text
"\\mscrA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\119966', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{C}"),(Text
"unicode-math",Text
"\\mscrC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\119967', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{D}"),(Text
"unicode-math",Text
"\\mscrD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\119970', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{G}"),(Text
"unicode-math",Text
"\\mscrG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\119973', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{J}"),(Text
"unicode-math",Text
"\\mscrJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\119974', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{K}"),(Text
"unicode-math",Text
"\\mscrK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\119977', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{N}"),(Text
"unicode-math",Text
"\\mscrN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\119978', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{O}"),(Text
"unicode-math",Text
"\\mscrO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\119979', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{P}"),(Text
"unicode-math",Text
"\\mscrP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\119980', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{Q}"),(Text
"unicode-math",Text
"\\mscrQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\119982', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{S}"),(Text
"unicode-math",Text
"\\mscrS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\119983', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{T}"),(Text
"unicode-math",Text
"\\mscrT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\119984', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{U}"),(Text
"unicode-math",Text
"\\mscrU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\119985', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{V}"),(Text
"unicode-math",Text
"\\mscrV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\119986', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{W}"),(Text
"unicode-math",Text
"\\mscrW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\119987', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{X}"),(Text
"unicode-math",Text
"\\mscrX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\119988', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{Y}"),(Text
"unicode-math",Text
"\\mscrY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\119989', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathcal{Z}"),(Text
"unicode-math",Text
"\\mscrZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\119990', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{a}"),(Text
"unicode-math",Text
"\\mscra")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL A"}
, Record {uchar :: Char
uchar = Char
'\119991', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{b}"),(Text
"unicode-math",Text
"\\mscrb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL B"}
, Record {uchar :: Char
uchar = Char
'\119992', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{c}"),(Text
"unicode-math",Text
"\\mscrc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL C"}
, Record {uchar :: Char
uchar = Char
'\119993', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{d}"),(Text
"unicode-math",Text
"\\mscrd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL D"}
, Record {uchar :: Char
uchar = Char
'\119995', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{f}"),(Text
"unicode-math",Text
"\\mscrf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL F"}
, Record {uchar :: Char
uchar = Char
'\119997', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{h}"),(Text
"unicode-math",Text
"\\mscrh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL H"}
, Record {uchar :: Char
uchar = Char
'\119998', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{i}"),(Text
"unicode-math",Text
"\\mscri")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL I"}
, Record {uchar :: Char
uchar = Char
'\119999', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{j}"),(Text
"unicode-math",Text
"\\mscrj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120000', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{k}"),(Text
"unicode-math",Text
"\\mscrk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120001', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{l}"),(Text
"unicode-math",Text
"\\mscrl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120002', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{m}"),(Text
"unicode-math",Text
"\\mscrm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120003', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{n}"),(Text
"unicode-math",Text
"\\mscrn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120005', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{p}"),(Text
"unicode-math",Text
"\\mscrp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120006', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{q}"),(Text
"unicode-math",Text
"\\mscrq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120007', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{r}"),(Text
"unicode-math",Text
"\\mscrr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120008', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{s}"),(Text
"unicode-math",Text
"\\mscrs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120009', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{t}"),(Text
"unicode-math",Text
"\\mscrt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120010', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{u}"),(Text
"unicode-math",Text
"\\mscru")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120011', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{v}"),(Text
"unicode-math",Text
"\\mscrv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120012', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{w}"),(Text
"unicode-math",Text
"\\mscrw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120013', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{x}"),(Text
"unicode-math",Text
"\\mscrx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120014', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{y}"),(Text
"unicode-math",Text
"\\mscry")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120015', commands :: [(Text, Text)]
commands = [(Text
"urwchancal",Text
"\\mathcal{z}"),(Text
"unicode-math",Text
"\\mscrz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SCRIPT SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120016', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120017', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120018', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\120019', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120020', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120021', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120022', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120023', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\120024', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120025', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120026', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120027', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120028', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120029', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120030', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120031', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120032', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120033', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\120034', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120035', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120036', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120037', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120038', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120039', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120040', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120041', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\120042', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscra")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120043', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120044', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120045', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120046', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscre")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120047', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120048', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120049', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120050', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscri")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120051', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120052', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120053', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120054', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120055', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120056', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscro")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120057', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120058', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120059', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120060', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120061', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120062', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscru")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120063', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120064', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120065', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120066', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscry")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120067', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfscrz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SCRIPT SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120068', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{A}"),(Text
"unicode-math",Text
"\\mfrakA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120069', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{B}"),(Text
"unicode-math",Text
"\\mfrakB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120071', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{D}"),(Text
"unicode-math",Text
"\\mfrakD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120072', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{E}"),(Text
"unicode-math",Text
"\\mfrakE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120073', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{F}"),(Text
"unicode-math",Text
"\\mfrakF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120074', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{G}"),(Text
"unicode-math",Text
"\\mfrakG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120077', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{J}"),(Text
"unicode-math",Text
"\\mfrakJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120078', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{K}"),(Text
"unicode-math",Text
"\\mfrakK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120079', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{L}"),(Text
"unicode-math",Text
"\\mfrakL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120080', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{M}"),(Text
"unicode-math",Text
"\\mfrakM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120081', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{N}"),(Text
"unicode-math",Text
"\\mfrakN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120082', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{O}"),(Text
"unicode-math",Text
"\\mfrakO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120083', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{P}"),(Text
"unicode-math",Text
"\\mfrakP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120084', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{Q}"),(Text
"unicode-math",Text
"\\mfrakQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120086', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{S}"),(Text
"unicode-math",Text
"\\mfrakS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120087', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{T}"),(Text
"unicode-math",Text
"\\mfrakT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120088', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{U}"),(Text
"unicode-math",Text
"\\mfrakU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120089', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{V}"),(Text
"unicode-math",Text
"\\mfrakV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120090', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{W}"),(Text
"unicode-math",Text
"\\mfrakW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120091', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{X}"),(Text
"unicode-math",Text
"\\mfrakX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120092', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{Y}"),(Text
"unicode-math",Text
"\\mfrakY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120094', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{a}"),(Text
"unicode-math",Text
"\\mfraka")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120095', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{b}"),(Text
"unicode-math",Text
"\\mfrakb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120096', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{c}"),(Text
"unicode-math",Text
"\\mfrakc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120097', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{d}"),(Text
"unicode-math",Text
"\\mfrakd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120098', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{e}"),(Text
"unicode-math",Text
"\\mfrake")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120099', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{f}"),(Text
"unicode-math",Text
"\\mfrakf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120100', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{g}"),(Text
"unicode-math",Text
"\\mfrakg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120101', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{h}"),(Text
"unicode-math",Text
"\\mfrakh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120102', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{i}"),(Text
"unicode-math",Text
"\\mfraki")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120103', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{j}"),(Text
"unicode-math",Text
"\\mfrakj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120104', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{k}"),(Text
"unicode-math",Text
"\\mfrakk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120105', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{l}"),(Text
"unicode-math",Text
"\\mfrakl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120106', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{m}"),(Text
"unicode-math",Text
"\\mfrakm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120107', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{n}"),(Text
"unicode-math",Text
"\\mfrakn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120108', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{o}"),(Text
"unicode-math",Text
"\\mfrako")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120109', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{p}"),(Text
"unicode-math",Text
"\\mfrakp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120110', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{q}"),(Text
"unicode-math",Text
"\\mfrakq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120111', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{r}"),(Text
"unicode-math",Text
"\\mfrakr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120112', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{s}"),(Text
"unicode-math",Text
"\\mfraks")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120113', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{t}"),(Text
"unicode-math",Text
"\\mfrakt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120114', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{u}"),(Text
"unicode-math",Text
"\\mfraku")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120115', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{v}"),(Text
"unicode-math",Text
"\\mfrakv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120116', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{w}"),(Text
"unicode-math",Text
"\\mfrakw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120117', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{x}"),(Text
"unicode-math",Text
"\\mfrakx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120118', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{y}"),(Text
"unicode-math",Text
"\\mfraky")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120119', commands :: [(Text, Text)]
commands = [(Text
"eufrak",Text
"\\mathfrak{z}"),(Text
"unicode-math",Text
"\\mfrakz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL FRAKTUR SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120120', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{A}"),(Text
"dsfont",Text
"\\mathds{A}"),(Text
"unicode-math",Text
"\\BbbA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120121', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{B}"),(Text
"dsfont",Text
"\\mathds{B}"),(Text
"unicode-math",Text
"\\BbbB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120123', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{D}"),(Text
"dsfont",Text
"\\mathds{D}"),(Text
"unicode-math",Text
"\\BbbD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120124', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{E}"),(Text
"dsfont",Text
"\\mathds{E}"),(Text
"unicode-math",Text
"\\BbbE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120125', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{F}"),(Text
"dsfont",Text
"\\mathds{F}"),(Text
"unicode-math",Text
"\\BbbF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120126', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{G}"),(Text
"dsfont",Text
"\\mathds{G}"),(Text
"unicode-math",Text
"\\BbbG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120128', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{I}"),(Text
"dsfont",Text
"\\mathds{I}"),(Text
"unicode-math",Text
"\\BbbI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120129', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{J}"),(Text
"dsfont",Text
"\\mathds{J}"),(Text
"unicode-math",Text
"\\BbbJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120130', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{K}"),(Text
"dsfont",Text
"\\mathds{K}"),(Text
"unicode-math",Text
"\\BbbK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120131', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{L}"),(Text
"dsfont",Text
"\\mathds{L}"),(Text
"unicode-math",Text
"\\BbbL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120132', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{M}"),(Text
"dsfont",Text
"\\mathds{M}"),(Text
"unicode-math",Text
"\\BbbM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120134', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{O}"),(Text
"dsfont",Text
"\\mathds{O}"),(Text
"unicode-math",Text
"\\BbbO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120138', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{S}"),(Text
"dsfont",Text
"\\mathds{S}"),(Text
"unicode-math",Text
"\\BbbS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120139', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{T}"),(Text
"dsfont",Text
"\\mathds{T}"),(Text
"unicode-math",Text
"\\BbbT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120140', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{U}"),(Text
"dsfont",Text
"\\mathds{U}"),(Text
"unicode-math",Text
"\\BbbU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120141', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{V}"),(Text
"dsfont",Text
"\\mathds{V}"),(Text
"unicode-math",Text
"\\BbbV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120142', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{W}"),(Text
"dsfont",Text
"\\mathds{W}"),(Text
"unicode-math",Text
"\\BbbW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120143', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{X}"),(Text
"dsfont",Text
"\\mathds{X}"),(Text
"unicode-math",Text
"\\BbbX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120144', commands :: [(Text, Text)]
commands = [(Text
"mathbb",Text
"\\mathbb{Y}"),(Text
"dsfont",Text
"\\mathds{Y}"),(Text
"unicode-math",Text
"\\BbbY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"matMATHEMATICAL DOUBLE-STRUCK CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120146', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{a}"),(Text
"unicode-math",Text
"\\Bbba")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120147', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{b}"),(Text
"unicode-math",Text
"\\Bbbb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120148', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{c}"),(Text
"unicode-math",Text
"\\Bbbc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120149', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{d}"),(Text
"unicode-math",Text
"\\Bbbd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120150', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{e}"),(Text
"unicode-math",Text
"\\Bbbe")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120151', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{f}"),(Text
"unicode-math",Text
"\\Bbbf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120152', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{g}"),(Text
"unicode-math",Text
"\\Bbbg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120153', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{h}"),(Text
"unicode-math",Text
"\\Bbbh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120154', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{i}"),(Text
"unicode-math",Text
"\\Bbbi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120155', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{j}"),(Text
"unicode-math",Text
"\\Bbbj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120156', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{k}"),(Text
"fourier",Text
"\\mathbb{k}"),(Text
"amssymb",Text
"\\Bbbk"),(Text
"unicode-math",Text
"\\Bbbk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120157', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{l}"),(Text
"unicode-math",Text
"\\Bbbl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120158', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{m}"),(Text
"unicode-math",Text
"\\Bbbm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120159', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{n}"),(Text
"unicode-math",Text
"\\Bbbn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120160', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{o}"),(Text
"unicode-math",Text
"\\Bbbo")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120161', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{p}"),(Text
"unicode-math",Text
"\\Bbbp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120162', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{q}"),(Text
"unicode-math",Text
"\\Bbbq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120163', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{r}"),(Text
"unicode-math",Text
"\\Bbbr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120164', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{s}"),(Text
"unicode-math",Text
"\\Bbbs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120165', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{t}"),(Text
"unicode-math",Text
"\\Bbbt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120166', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{u}"),(Text
"unicode-math",Text
"\\Bbbu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120167', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{v}"),(Text
"unicode-math",Text
"\\Bbbv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120168', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{w}"),(Text
"unicode-math",Text
"\\Bbbw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120169', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{x}"),(Text
"unicode-math",Text
"\\Bbbx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120170', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{y}"),(Text
"unicode-math",Text
"\\Bbby")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120171', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{z}"),(Text
"unicode-math",Text
"\\Bbbz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL DOUBLE-STRUCK SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120172', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120173', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120174', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\120175', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120176', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120177', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120178', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120179', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\120180', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120181', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120182', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120183', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120184', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120185', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120186', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120187', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120188', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120189', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\120190', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120191', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120192', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120193', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120194', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120195', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120196', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120197', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\120198', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffraka")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120199', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120200', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120201', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120202', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrake")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120203', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120204', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120205', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120206', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffraki")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120207', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120208', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120209', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120210', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120211', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120212', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrako")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120213', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120214', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120215', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120216', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffraks")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120217', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120218', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffraku")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120219', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120220', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120221', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120222', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffraky")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120223', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbffrakz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD FRAKTUR SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120224', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{A}"),(Text
"unicode-math",Text
"\\msansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120225', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{B}"),(Text
"unicode-math",Text
"\\msansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120226', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{C}"),(Text
"unicode-math",Text
"\\msansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\120227', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{D}"),(Text
"unicode-math",Text
"\\msansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120228', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{E}"),(Text
"unicode-math",Text
"\\msansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120229', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{F}"),(Text
"unicode-math",Text
"\\msansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120230', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{G}"),(Text
"unicode-math",Text
"\\msansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120231', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{H}"),(Text
"unicode-math",Text
"\\msansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\120232', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{I}"),(Text
"unicode-math",Text
"\\msansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120233', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{J}"),(Text
"unicode-math",Text
"\\msansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120234', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{K}"),(Text
"unicode-math",Text
"\\msansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120235', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{L}"),(Text
"unicode-math",Text
"\\msansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120236', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{M}"),(Text
"unicode-math",Text
"\\msansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120237', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{N}"),(Text
"unicode-math",Text
"\\msansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120238', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{O}"),(Text
"unicode-math",Text
"\\msansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120239', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{P}"),(Text
"unicode-math",Text
"\\msansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120240', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{Q}"),(Text
"unicode-math",Text
"\\msansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120241', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{R}"),(Text
"unicode-math",Text
"\\msansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\120242', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{S}"),(Text
"unicode-math",Text
"\\msansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120243', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{T}"),(Text
"unicode-math",Text
"\\msansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120244', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{U}"),(Text
"unicode-math",Text
"\\msansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120245', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{V}"),(Text
"unicode-math",Text
"\\msansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120246', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{W}"),(Text
"unicode-math",Text
"\\msansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120247', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{X}"),(Text
"unicode-math",Text
"\\msansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120248', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{Y}"),(Text
"unicode-math",Text
"\\msansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120249', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{Z}"),(Text
"unicode-math",Text
"\\msansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\120250', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{a}"),(Text
"unicode-math",Text
"\\msansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120251', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{b}"),(Text
"unicode-math",Text
"\\msansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120252', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{c}"),(Text
"unicode-math",Text
"\\msansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120253', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{d}"),(Text
"unicode-math",Text
"\\msansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120254', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{e}"),(Text
"unicode-math",Text
"\\msanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120255', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{f}"),(Text
"unicode-math",Text
"\\msansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120256', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{g}"),(Text
"unicode-math",Text
"\\msansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120257', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{h}"),(Text
"unicode-math",Text
"\\msansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120258', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{i}"),(Text
"unicode-math",Text
"\\msansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120259', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{j}"),(Text
"unicode-math",Text
"\\msansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120260', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{k}"),(Text
"unicode-math",Text
"\\msansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120261', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{l}"),(Text
"unicode-math",Text
"\\msansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120262', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{m}"),(Text
"unicode-math",Text
"\\msansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120263', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{n}"),(Text
"unicode-math",Text
"\\msansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120264', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{o}"),(Text
"unicode-math",Text
"\\msanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120265', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{p}"),(Text
"unicode-math",Text
"\\msansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120266', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{q}"),(Text
"unicode-math",Text
"\\msansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120267', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{r}"),(Text
"unicode-math",Text
"\\msansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120268', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{s}"),(Text
"unicode-math",Text
"\\msanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120269', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{t}"),(Text
"unicode-math",Text
"\\msanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120270', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{u}"),(Text
"unicode-math",Text
"\\msansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120271', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{v}"),(Text
"unicode-math",Text
"\\msansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120272', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{w}"),(Text
"unicode-math",Text
"\\msansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120273', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{x}"),(Text
"unicode-math",Text
"\\msansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120274', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{y}"),(Text
"unicode-math",Text
"\\msansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120275', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{z}"),(Text
"unicode-math",Text
"\\msansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120276', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{A}"),(Text
"unicode-math",Text
"\\mbfsansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120277', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{B}"),(Text
"unicode-math",Text
"\\mbfsansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120278', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{C}"),(Text
"unicode-math",Text
"\\mbfsansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\120279', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{D}"),(Text
"unicode-math",Text
"\\mbfsansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120280', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{E}"),(Text
"unicode-math",Text
"\\mbfsansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120281', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{F}"),(Text
"unicode-math",Text
"\\mbfsansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120282', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{G}"),(Text
"unicode-math",Text
"\\mbfsansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120283', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{H}"),(Text
"unicode-math",Text
"\\mbfsansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\120284', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{I}"),(Text
"unicode-math",Text
"\\mbfsansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120285', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{J}"),(Text
"unicode-math",Text
"\\mbfsansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120286', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{K}"),(Text
"unicode-math",Text
"\\mbfsansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120287', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{L}"),(Text
"unicode-math",Text
"\\mbfsansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120288', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{M}"),(Text
"unicode-math",Text
"\\mbfsansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120289', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{N}"),(Text
"unicode-math",Text
"\\mbfsansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120290', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{O}"),(Text
"unicode-math",Text
"\\mbfsansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120291', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{P}"),(Text
"unicode-math",Text
"\\mbfsansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120292', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{Q}"),(Text
"unicode-math",Text
"\\mbfsansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120293', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{R}"),(Text
"unicode-math",Text
"\\mbfsansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\120294', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{S}"),(Text
"unicode-math",Text
"\\mbfsansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120295', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{T}"),(Text
"unicode-math",Text
"\\mbfsansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120296', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{U}"),(Text
"unicode-math",Text
"\\mbfsansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120297', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{V}"),(Text
"unicode-math",Text
"\\mbfsansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120298', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{W}"),(Text
"unicode-math",Text
"\\mbfsansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120299', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{X}"),(Text
"unicode-math",Text
"\\mbfsansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120300', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{Y}"),(Text
"unicode-math",Text
"\\mbfsansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120301', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{Z}"),(Text
"unicode-math",Text
"\\mbfsansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\120302', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{a}"),(Text
"unicode-math",Text
"\\mbfsansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120303', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{b}"),(Text
"unicode-math",Text
"\\mbfsansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120304', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{c}"),(Text
"unicode-math",Text
"\\mbfsansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120305', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{d}"),(Text
"unicode-math",Text
"\\mbfsansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120306', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{e}"),(Text
"unicode-math",Text
"\\mbfsanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120307', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{f}"),(Text
"unicode-math",Text
"\\mbfsansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120308', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{g}"),(Text
"unicode-math",Text
"\\mbfsansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120309', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{h}"),(Text
"unicode-math",Text
"\\mbfsansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120310', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{i}"),(Text
"unicode-math",Text
"\\mbfsansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120311', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{j}"),(Text
"unicode-math",Text
"\\mbfsansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120312', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{k}"),(Text
"unicode-math",Text
"\\mbfsansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120313', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{l}"),(Text
"unicode-math",Text
"\\mbfsansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120314', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{m}"),(Text
"unicode-math",Text
"\\mbfsansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120315', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{n}"),(Text
"unicode-math",Text
"\\mbfsansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120316', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{o}"),(Text
"unicode-math",Text
"\\mbfsanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120317', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{p}"),(Text
"unicode-math",Text
"\\mbfsansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120318', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{q}"),(Text
"unicode-math",Text
"\\mbfsansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120319', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{r}"),(Text
"unicode-math",Text
"\\mbfsansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120320', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{s}"),(Text
"unicode-math",Text
"\\mbfsanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120321', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{t}"),(Text
"unicode-math",Text
"\\mbfsanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120322', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{u}"),(Text
"unicode-math",Text
"\\mbfsansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120323', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{v}"),(Text
"unicode-math",Text
"\\mbfsansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120324', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{w}"),(Text
"unicode-math",Text
"\\mbfsansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120325', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{x}"),(Text
"unicode-math",Text
"\\mbfsansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120326', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{y}"),(Text
"unicode-math",Text
"\\mbfsansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120327', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{z}"),(Text
"unicode-math",Text
"\\mbfsansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120328', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{A}"),(Text
"unicode-math",Text
"\\mitsansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120329', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{B}"),(Text
"unicode-math",Text
"\\mitsansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120330', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{C}"),(Text
"unicode-math",Text
"\\mitsansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\120331', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{D}"),(Text
"unicode-math",Text
"\\mitsansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120332', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{E}"),(Text
"unicode-math",Text
"\\mitsansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120333', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{F}"),(Text
"unicode-math",Text
"\\mitsansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120334', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{G}"),(Text
"unicode-math",Text
"\\mitsansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120335', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{H}"),(Text
"unicode-math",Text
"\\mitsansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\120336', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{I}"),(Text
"unicode-math",Text
"\\mitsansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120337', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{J}"),(Text
"unicode-math",Text
"\\mitsansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120338', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{K}"),(Text
"unicode-math",Text
"\\mitsansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120339', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{L}"),(Text
"unicode-math",Text
"\\mitsansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120340', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{M}"),(Text
"unicode-math",Text
"\\mitsansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120341', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{N}"),(Text
"unicode-math",Text
"\\mitsansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120342', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{O}"),(Text
"unicode-math",Text
"\\mitsansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120343', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{P}"),(Text
"unicode-math",Text
"\\mitsansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120344', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{Q}"),(Text
"unicode-math",Text
"\\mitsansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120345', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{R}"),(Text
"unicode-math",Text
"\\mitsansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\120346', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{S}"),(Text
"unicode-math",Text
"\\mitsansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120347', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{T}"),(Text
"unicode-math",Text
"\\mitsansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120348', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{U}"),(Text
"unicode-math",Text
"\\mitsansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120349', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{V}"),(Text
"unicode-math",Text
"\\mitsansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120350', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{W}"),(Text
"unicode-math",Text
"\\mitsansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120351', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{X}"),(Text
"unicode-math",Text
"\\mitsansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120352', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{Y}"),(Text
"unicode-math",Text
"\\mitsansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120353', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{Z}"),(Text
"unicode-math",Text
"\\mitsansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\120354', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{a}"),(Text
"unicode-math",Text
"\\mitsansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120355', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{b}"),(Text
"unicode-math",Text
"\\mitsansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120356', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{c}"),(Text
"unicode-math",Text
"\\mitsansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120357', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{d}"),(Text
"unicode-math",Text
"\\mitsansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120358', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{e}"),(Text
"unicode-math",Text
"\\mitsanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120359', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{f}"),(Text
"unicode-math",Text
"\\mitsansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120360', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{g}"),(Text
"unicode-math",Text
"\\mitsansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120361', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{h}"),(Text
"unicode-math",Text
"\\mitsansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120362', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{i}"),(Text
"unicode-math",Text
"\\mitsansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120363', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{j}"),(Text
"unicode-math",Text
"\\mitsansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120364', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{k}"),(Text
"unicode-math",Text
"\\mitsansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120365', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{l}"),(Text
"unicode-math",Text
"\\mitsansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120366', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{m}"),(Text
"unicode-math",Text
"\\mitsansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120367', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{n}"),(Text
"unicode-math",Text
"\\mitsansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120368', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{o}"),(Text
"unicode-math",Text
"\\mitsanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120369', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{p}"),(Text
"unicode-math",Text
"\\mitsansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120370', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{q}"),(Text
"unicode-math",Text
"\\mitsansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120371', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{r}"),(Text
"unicode-math",Text
"\\mitsansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120372', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{s}"),(Text
"unicode-math",Text
"\\mitsanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120373', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{t}"),(Text
"unicode-math",Text
"\\mitsanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120374', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{u}"),(Text
"unicode-math",Text
"\\mitsansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120375', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{v}"),(Text
"unicode-math",Text
"\\mitsansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120376', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{w}"),(Text
"unicode-math",Text
"\\mitsansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120377', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{x}"),(Text
"unicode-math",Text
"\\mitsansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120378', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{y}"),(Text
"unicode-math",Text
"\\mitsansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120379', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfit",Text
"\\mathsfit{z}"),(Text
"unicode-math",Text
"\\mitsansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF ITALIC SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120380', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{A}"),(Text
"unicode-math",Text
"\\mbfitsansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120381', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{B}"),(Text
"unicode-math",Text
"\\mbfitsansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120382', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{C}"),(Text
"unicode-math",Text
"\\mbfitsansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\120383', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{D}"),(Text
"unicode-math",Text
"\\mbfitsansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120384', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{E}"),(Text
"unicode-math",Text
"\\mbfitsansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120385', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{F}"),(Text
"unicode-math",Text
"\\mbfitsansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120386', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{G}"),(Text
"unicode-math",Text
"\\mbfitsansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120387', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{H}"),(Text
"unicode-math",Text
"\\mbfitsansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\120388', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{I}"),(Text
"unicode-math",Text
"\\mbfitsansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120389', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{J}"),(Text
"unicode-math",Text
"\\mbfitsansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120390', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{K}"),(Text
"unicode-math",Text
"\\mbfitsansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120391', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{L}"),(Text
"unicode-math",Text
"\\mbfitsansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120392', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{M}"),(Text
"unicode-math",Text
"\\mbfitsansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120393', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{N}"),(Text
"unicode-math",Text
"\\mbfitsansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120394', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{O}"),(Text
"unicode-math",Text
"\\mbfitsansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120395', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{P}"),(Text
"unicode-math",Text
"\\mbfitsansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120396', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{Q}"),(Text
"unicode-math",Text
"\\mbfitsansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120397', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{R}"),(Text
"unicode-math",Text
"\\mbfitsansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\120398', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{S}"),(Text
"unicode-math",Text
"\\mbfitsansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120399', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{T}"),(Text
"unicode-math",Text
"\\mbfitsansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120400', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{U}"),(Text
"unicode-math",Text
"\\mbfitsansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120401', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{V}"),(Text
"unicode-math",Text
"\\mbfitsansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120402', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{W}"),(Text
"unicode-math",Text
"\\mbfitsansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120403', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{X}"),(Text
"unicode-math",Text
"\\mbfitsansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120404', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{Y}"),(Text
"unicode-math",Text
"\\mbfitsansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120405', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{Z}"),(Text
"unicode-math",Text
"\\mbfitsansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\120406', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{a}"),(Text
"unicode-math",Text
"\\mbfitsansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120407', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{b}"),(Text
"unicode-math",Text
"\\mbfitsansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120408', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{c}"),(Text
"unicode-math",Text
"\\mbfitsansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120409', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{d}"),(Text
"unicode-math",Text
"\\mbfitsansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120410', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{e}"),(Text
"unicode-math",Text
"\\mbfitsanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120411', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{f}"),(Text
"unicode-math",Text
"\\mbfitsansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120412', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{g}"),(Text
"unicode-math",Text
"\\mbfitsansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120413', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{h}"),(Text
"unicode-math",Text
"\\mbfitsansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120414', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{i}"),(Text
"unicode-math",Text
"\\mbfitsansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120415', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{j}"),(Text
"unicode-math",Text
"\\mbfitsansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120416', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{k}"),(Text
"unicode-math",Text
"\\mbfitsansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120417', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{l}"),(Text
"unicode-math",Text
"\\mbfitsansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120418', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{m}"),(Text
"unicode-math",Text
"\\mbfitsansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120419', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{n}"),(Text
"unicode-math",Text
"\\mbfitsansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120420', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{o}"),(Text
"unicode-math",Text
"\\mbfitsanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120421', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{p}"),(Text
"unicode-math",Text
"\\mbfitsansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120422', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{q}"),(Text
"unicode-math",Text
"\\mbfitsansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120423', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{r}"),(Text
"unicode-math",Text
"\\mbfitsansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120424', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{s}"),(Text
"unicode-math",Text
"\\mbfitsanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120425', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{t}"),(Text
"unicode-math",Text
"\\mbfitsanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120426', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{u}"),(Text
"unicode-math",Text
"\\mbfitsansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120427', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{v}"),(Text
"unicode-math",Text
"\\mbfitsansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120428', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{w}"),(Text
"unicode-math",Text
"\\mbfitsansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120429', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{x}"),(Text
"unicode-math",Text
"\\mbfitsansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120430', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{y}"),(Text
"unicode-math",Text
"\\mbfitsansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120431', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{z}"),(Text
"unicode-math",Text
"\\mbfitsansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120432', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{A}"),(Text
"unicode-math",Text
"\\mttA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL A"}
, Record {uchar :: Char
uchar = Char
'\120433', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{B}"),(Text
"unicode-math",Text
"\\mttB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL B"}
, Record {uchar :: Char
uchar = Char
'\120434', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{C}"),(Text
"unicode-math",Text
"\\mttC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL C"}
, Record {uchar :: Char
uchar = Char
'\120435', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{D}"),(Text
"unicode-math",Text
"\\mttD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL D"}
, Record {uchar :: Char
uchar = Char
'\120436', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{E}"),(Text
"unicode-math",Text
"\\mttE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL E"}
, Record {uchar :: Char
uchar = Char
'\120437', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{F}"),(Text
"unicode-math",Text
"\\mttF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL F"}
, Record {uchar :: Char
uchar = Char
'\120438', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{G}"),(Text
"unicode-math",Text
"\\mttG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL G"}
, Record {uchar :: Char
uchar = Char
'\120439', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{H}"),(Text
"unicode-math",Text
"\\mttH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL H"}
, Record {uchar :: Char
uchar = Char
'\120440', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{I}"),(Text
"unicode-math",Text
"\\mttI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL I"}
, Record {uchar :: Char
uchar = Char
'\120441', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{J}"),(Text
"unicode-math",Text
"\\mttJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL J"}
, Record {uchar :: Char
uchar = Char
'\120442', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{K}"),(Text
"unicode-math",Text
"\\mttK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL K"}
, Record {uchar :: Char
uchar = Char
'\120443', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{L}"),(Text
"unicode-math",Text
"\\mttL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL L"}
, Record {uchar :: Char
uchar = Char
'\120444', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{M}"),(Text
"unicode-math",Text
"\\mttM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL M"}
, Record {uchar :: Char
uchar = Char
'\120445', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{N}"),(Text
"unicode-math",Text
"\\mttN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL N"}
, Record {uchar :: Char
uchar = Char
'\120446', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{O}"),(Text
"unicode-math",Text
"\\mttO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL O"}
, Record {uchar :: Char
uchar = Char
'\120447', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{P}"),(Text
"unicode-math",Text
"\\mttP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL P"}
, Record {uchar :: Char
uchar = Char
'\120448', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{Q}"),(Text
"unicode-math",Text
"\\mttQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL Q"}
, Record {uchar :: Char
uchar = Char
'\120449', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{R}"),(Text
"unicode-math",Text
"\\mttR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL R"}
, Record {uchar :: Char
uchar = Char
'\120450', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{S}"),(Text
"unicode-math",Text
"\\mttS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL S"}
, Record {uchar :: Char
uchar = Char
'\120451', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{T}"),(Text
"unicode-math",Text
"\\mttT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL T"}
, Record {uchar :: Char
uchar = Char
'\120452', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{U}"),(Text
"unicode-math",Text
"\\mttU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL U"}
, Record {uchar :: Char
uchar = Char
'\120453', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{V}"),(Text
"unicode-math",Text
"\\mttV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL V"}
, Record {uchar :: Char
uchar = Char
'\120454', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{W}"),(Text
"unicode-math",Text
"\\mttW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL W"}
, Record {uchar :: Char
uchar = Char
'\120455', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{X}"),(Text
"unicode-math",Text
"\\mttX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL X"}
, Record {uchar :: Char
uchar = Char
'\120456', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{Y}"),(Text
"unicode-math",Text
"\\mttY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL Y"}
, Record {uchar :: Char
uchar = Char
'\120457', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{Z}"),(Text
"unicode-math",Text
"\\mttZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE CAPITAL Z"}
, Record {uchar :: Char
uchar = Char
'\120458', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{a}"),(Text
"unicode-math",Text
"\\mtta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL A"}
, Record {uchar :: Char
uchar = Char
'\120459', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{b}"),(Text
"unicode-math",Text
"\\mttb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL B"}
, Record {uchar :: Char
uchar = Char
'\120460', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{c}"),(Text
"unicode-math",Text
"\\mttc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL C"}
, Record {uchar :: Char
uchar = Char
'\120461', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{d}"),(Text
"unicode-math",Text
"\\mttd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL D"}
, Record {uchar :: Char
uchar = Char
'\120462', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{e}"),(Text
"unicode-math",Text
"\\mtte")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL E"}
, Record {uchar :: Char
uchar = Char
'\120463', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{f}"),(Text
"unicode-math",Text
"\\mttf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL F"}
, Record {uchar :: Char
uchar = Char
'\120464', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{g}"),(Text
"unicode-math",Text
"\\mttg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL G"}
, Record {uchar :: Char
uchar = Char
'\120465', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{h}"),(Text
"unicode-math",Text
"\\mtth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL H"}
, Record {uchar :: Char
uchar = Char
'\120466', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{i}"),(Text
"unicode-math",Text
"\\mtti")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL I"}
, Record {uchar :: Char
uchar = Char
'\120467', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{j}"),(Text
"unicode-math",Text
"\\mttj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL J"}
, Record {uchar :: Char
uchar = Char
'\120468', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{k}"),(Text
"unicode-math",Text
"\\mttk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL K"}
, Record {uchar :: Char
uchar = Char
'\120469', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{l}"),(Text
"unicode-math",Text
"\\mttl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL L"}
, Record {uchar :: Char
uchar = Char
'\120470', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{m}"),(Text
"unicode-math",Text
"\\mttm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL M"}
, Record {uchar :: Char
uchar = Char
'\120471', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{n}"),(Text
"unicode-math",Text
"\\mttn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL N"}
, Record {uchar :: Char
uchar = Char
'\120472', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{o}"),(Text
"unicode-math",Text
"\\mtto")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL O"}
, Record {uchar :: Char
uchar = Char
'\120473', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{p}"),(Text
"unicode-math",Text
"\\mttp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL P"}
, Record {uchar :: Char
uchar = Char
'\120474', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{q}"),(Text
"unicode-math",Text
"\\mttq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL Q"}
, Record {uchar :: Char
uchar = Char
'\120475', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{r}"),(Text
"unicode-math",Text
"\\mttr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL R"}
, Record {uchar :: Char
uchar = Char
'\120476', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{s}"),(Text
"unicode-math",Text
"\\mtts")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL S"}
, Record {uchar :: Char
uchar = Char
'\120477', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{t}"),(Text
"unicode-math",Text
"\\mttt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL T"}
, Record {uchar :: Char
uchar = Char
'\120478', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{u}"),(Text
"unicode-math",Text
"\\mttu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL U"}
, Record {uchar :: Char
uchar = Char
'\120479', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{v}"),(Text
"unicode-math",Text
"\\mttv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL V"}
, Record {uchar :: Char
uchar = Char
'\120480', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{w}"),(Text
"unicode-math",Text
"\\mttw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL W"}
, Record {uchar :: Char
uchar = Char
'\120481', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{x}"),(Text
"unicode-math",Text
"\\mttx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL X"}
, Record {uchar :: Char
uchar = Char
'\120482', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{y}"),(Text
"unicode-math",Text
"\\mtty")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL Y"}
, Record {uchar :: Char
uchar = Char
'\120483', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{z}"),(Text
"unicode-math",Text
"\\mttz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL MONOSPACE SMALL Z"}
, Record {uchar :: Char
uchar = Char
'\120484', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\imath"),(Text
"unicode-math",Text
"\\imath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL DOTLESS I"}
, Record {uchar :: Char
uchar = Char
'\120485', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\jmath"),(Text
"unicode-math",Text
"\\jmath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL DOTLESS J"}
, Record {uchar :: Char
uchar = Char
'\120488', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120489', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL BETA"}
, Record {uchar :: Char
uchar = Char
'\120490', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Gamma}"),(Text
"unicode-math",Text
"\\mbfGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120491', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Delta}"),(Text
"unicode-math",Text
"\\mbfDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120492', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120493', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120494', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL ETA"}
, Record {uchar :: Char
uchar = Char
'\120495', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Theta}"),(Text
"unicode-math",Text
"\\mbfTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL THETA"}
, Record {uchar :: Char
uchar = Char
'\120496', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120497', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120498', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Lambda}"),(Text
"unicode-math",Text
"\\mbfLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical bold capital lambda"}
, Record {uchar :: Char
uchar = Char
'\120499', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL MU"}
, Record {uchar :: Char
uchar = Char
'\120500', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL NU"}
, Record {uchar :: Char
uchar = Char
'\120501', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Xi}"),(Text
"unicode-math",Text
"\\mbfXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL XI"}
, Record {uchar :: Char
uchar = Char
'\120502', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120503', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Pi}"),(Text
"unicode-math",Text
"\\mbfPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL PI"}
, Record {uchar :: Char
uchar = Char
'\120504', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL RHO"}
, Record {uchar :: Char
uchar = Char
'\120505', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120506', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Sigma}"),(Text
"unicode-math",Text
"\\mbfSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120507', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL TAU"}
, Record {uchar :: Char
uchar = Char
'\120508', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Upsilon}"),(Text
"unicode-math",Text
"\\mbfUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120509', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Phi}"),(Text
"unicode-math",Text
"\\mbfPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL PHI"}
, Record {uchar :: Char
uchar = Char
'\120510', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL CHI"}
, Record {uchar :: Char
uchar = Char
'\120511', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Psi}"),(Text
"unicode-math",Text
"\\mbfPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL PSI"}
, Record {uchar :: Char
uchar = Char
'\120512', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{\\Omega}"),(Text
"unicode-math",Text
"\\mbfOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120513', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL BOLD NABLA"}
, Record {uchar :: Char
uchar = Char
'\120514', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\alpha}"),(Text
"unicode-math",Text
"\\mbfalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120515', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\beta}"),(Text
"unicode-math",Text
"\\mbfbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL BETA"}
, Record {uchar :: Char
uchar = Char
'\120516', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\gamma}"),(Text
"unicode-math",Text
"\\mbfgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120517', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\delta}"),(Text
"unicode-math",Text
"\\mbfdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120518', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\varepsilon}"),(Text
"unicode-math",Text
"\\mbfepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120519', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\zeta}"),(Text
"unicode-math",Text
"\\mbfzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120520', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\eta}"),(Text
"unicode-math",Text
"\\mbfeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL ETA"}
, Record {uchar :: Char
uchar = Char
'\120521', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\theta}"),(Text
"unicode-math",Text
"\\mbftheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL THETA"}
, Record {uchar :: Char
uchar = Char
'\120522', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\iota}"),(Text
"unicode-math",Text
"\\mbfiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120523', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\kappa}"),(Text
"unicode-math",Text
"\\mbfkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120524', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\lambda}"),(Text
"unicode-math",Text
"\\mbflambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical bold small lambda"}
, Record {uchar :: Char
uchar = Char
'\120525', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\mu}"),(Text
"unicode-math",Text
"\\mbfmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL MU"}
, Record {uchar :: Char
uchar = Char
'\120526', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\nu}"),(Text
"unicode-math",Text
"\\mbfnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL NU"}
, Record {uchar :: Char
uchar = Char
'\120527', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\xi}"),(Text
"unicode-math",Text
"\\mbfxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL XI"}
, Record {uchar :: Char
uchar = Char
'\120528', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120529', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\pi}"),(Text
"unicode-math",Text
"\\mbfpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL PI"}
, Record {uchar :: Char
uchar = Char
'\120530', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\rho}"),(Text
"unicode-math",Text
"\\mbfrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL RHO"}
, Record {uchar :: Char
uchar = Char
'\120531', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\varsigma}"),(Text
"unicode-math",Text
"\\mbfvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL FINAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120532', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\sigma}"),(Text
"unicode-math",Text
"\\mbfsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120533', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\tau}"),(Text
"unicode-math",Text
"\\mbftau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL TAU"}
, Record {uchar :: Char
uchar = Char
'\120534', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\upsilon}"),(Text
"unicode-math",Text
"\\mbfupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120535', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\varphi}"),(Text
"unicode-math",Text
"\\mbfvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL PHI"}
, Record {uchar :: Char
uchar = Char
'\120536', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\chi}"),(Text
"unicode-math",Text
"\\mbfchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL CHI"}
, Record {uchar :: Char
uchar = Char
'\120537', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\psi}"),(Text
"unicode-math",Text
"\\mbfpsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL PSI"}
, Record {uchar :: Char
uchar = Char
'\120538', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\omega}"),(Text
"unicode-math",Text
"\\mbfomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120539', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfpartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL BOLD PARTIAL DIFFERENTIAL"}
, Record {uchar :: Char
uchar = Char
'\120540', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\epsilon}"),(Text
"unicode-math",Text
"\\mbfvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD EPSILON SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120541', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\vartheta}"),(Text
"unicode-math",Text
"\\mbfvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120542', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD KAPPA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120543', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\phi}"),(Text
"unicode-math",Text
"\\mbfphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD PHI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120544', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\varrho}"),(Text
"unicode-math",Text
"\\mbfvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD RHO SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120545', commands :: [(Text, Text)]
commands = [(Text
"omlmathbf",Text
"\\mathbf{\\varpi}"),(Text
"unicode-math",Text
"\\mbfvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD PI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120546', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120547', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL BETA"}
, Record {uchar :: Char
uchar = Char
'\120548', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Gamma"),(Text
"-fourier",Text
"\\mathit{\\Gamma}"),(Text
"unicode-math",Text
"\\mitGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varGamma (amsmath fourier), MATHEMATICAL ITALIC CAPITAL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120549', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Delta"),(Text
"-fourier",Text
"\\mathit{\\Delta}"),(Text
"unicode-math",Text
"\\mitDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varDelta (amsmath fourier), MATHEMATICAL ITALIC CAPITAL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120550', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120551', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120552', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL ETA"}
, Record {uchar :: Char
uchar = Char
'\120553', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Theta"),(Text
"-fourier",Text
"\\mathit{\\Theta}"),(Text
"unicode-math",Text
"\\mitTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varTheta (amsmath fourier), MATHEMATICAL ITALIC CAPITAL THETA"}
, Record {uchar :: Char
uchar = Char
'\120554', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120555', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120556', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Lambda"),(Text
"-fourier",Text
"\\mathit{\\Lambda}"),(Text
"unicode-math",Text
"\\mitLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varLambda (amsmath fourier), mathematical italic capital lambda"}
, Record {uchar :: Char
uchar = Char
'\120557', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL MU"}
, Record {uchar :: Char
uchar = Char
'\120558', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL NU"}
, Record {uchar :: Char
uchar = Char
'\120559', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Xi"),(Text
"-fourier",Text
"\\mathit{\\Xi}"),(Text
"unicode-math",Text
"\\mitXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varXi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL XI"}
, Record {uchar :: Char
uchar = Char
'\120560', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120561', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Pi"),(Text
"-fourier",Text
"\\mathit{\\Pi}"),(Text
"unicode-math",Text
"\\mitPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varPi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL PI"}
, Record {uchar :: Char
uchar = Char
'\120562', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL RHO"}
, Record {uchar :: Char
uchar = Char
'\120563', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120564', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Sigma"),(Text
"-fourier",Text
"\\mathit{\\Sigma}"),(Text
"unicode-math",Text
"\\mitSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varSigma (amsmath fourier), MATHEMATICAL ITALIC CAPITAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120565', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL TAU"}
, Record {uchar :: Char
uchar = Char
'\120566', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Upsilon"),(Text
"-fourier",Text
"\\mathit{\\Upsilon}"),(Text
"unicode-math",Text
"\\mitUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varUpsilon (amsmath fourier), MATHEMATICAL ITALIC CAPITAL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120567', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Phi"),(Text
"-fourier",Text
"\\mathit{\\Phi}"),(Text
"unicode-math",Text
"\\mitPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varPhi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL PHI"}
, Record {uchar :: Char
uchar = Char
'\120568', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC CAPITAL CHI"}
, Record {uchar :: Char
uchar = Char
'\120569', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Psi"),(Text
"-fourier",Text
"\\mathit{\\Psi}"),(Text
"unicode-math",Text
"\\mitPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varPsi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL PSI"}
, Record {uchar :: Char
uchar = Char
'\120570', commands :: [(Text, Text)]
commands = [(Text
"slantedGreek",Text
"\\Omega"),(Text
"-fourier",Text
"\\mathit{\\Omega}"),(Text
"unicode-math",Text
"\\mitOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"= \\varOmega (amsmath fourier), MATHEMATICAL ITALIC CAPITAL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120571', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL ITALIC NABLA"}
, Record {uchar :: Char
uchar = Char
'\120572', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\alpha"),(Text
"omlmathit",Text
"\\mathit{\\alpha}"),(Text
"unicode-math",Text
"\\mitalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120573', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\beta"),(Text
"omlmathit",Text
"\\mathit{\\beta}"),(Text
"unicode-math",Text
"\\mitbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL BETA"}
, Record {uchar :: Char
uchar = Char
'\120574', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\gamma"),(Text
"omlmathit",Text
"\\mathit{\\gamma}"),(Text
"unicode-math",Text
"\\mitgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120575', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\delta"),(Text
"omlmathit",Text
"\\mathit{\\delta}"),(Text
"unicode-math",Text
"\\mitdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120576', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varepsilon"),(Text
"omlmathit",Text
"\\mathit{\\varepsilon}"),(Text
"unicode-math",Text
"\\mitepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120577', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\zeta"),(Text
"omlmathit",Text
"\\mathit{\\zeta}"),(Text
"unicode-math",Text
"\\mitzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120578', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\eta"),(Text
"omlmathit",Text
"\\mathit{\\eta}"),(Text
"unicode-math",Text
"\\miteta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL ETA"}
, Record {uchar :: Char
uchar = Char
'\120579', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\theta"),(Text
"omlmathit",Text
"\\mathit{\\theta}"),(Text
"unicode-math",Text
"\\mittheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL THETA"}
, Record {uchar :: Char
uchar = Char
'\120580', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\iota"),(Text
"omlmathit",Text
"\\mathit{\\iota}"),(Text
"unicode-math",Text
"\\mitiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120581', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\kappa"),(Text
"omlmathit",Text
"\\mathit{\\kappa}"),(Text
"unicode-math",Text
"\\mitkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120582', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\lambda"),(Text
"omlmathit",Text
"\\mathit{\\lambda}"),(Text
"unicode-math",Text
"\\mitlambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical italic small lambda"}
, Record {uchar :: Char
uchar = Char
'\120583', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mu"),(Text
"omlmathit",Text
"\\mathit{\\mu}"),(Text
"unicode-math",Text
"\\mitmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL MU"}
, Record {uchar :: Char
uchar = Char
'\120584', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\nu"),(Text
"omlmathit",Text
"\\mathit{\\nu}"),(Text
"unicode-math",Text
"\\mitnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL NU"}
, Record {uchar :: Char
uchar = Char
'\120585', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\xi"),(Text
"omlmathit",Text
"\\mathit{\\xi}"),(Text
"unicode-math",Text
"\\mitxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL XI"}
, Record {uchar :: Char
uchar = Char
'\120586', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mitomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120587', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\pi"),(Text
"omlmathit",Text
"\\mathit{\\pi}"),(Text
"unicode-math",Text
"\\mitpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL PI"}
, Record {uchar :: Char
uchar = Char
'\120588', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\rho"),(Text
"omlmathit",Text
"\\mathit{\\rho}"),(Text
"unicode-math",Text
"\\mitrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL RHO"}
, Record {uchar :: Char
uchar = Char
'\120589', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varsigma"),(Text
"omlmathit",Text
"\\mathit{\\varsigma}"),(Text
"unicode-math",Text
"\\mitvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL FINAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120590', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\sigma"),(Text
"omlmathit",Text
"\\mathit{\\sigma}"),(Text
"unicode-math",Text
"\\mitsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120591', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\tau"),(Text
"omlmathit",Text
"\\mathit{\\tau}"),(Text
"unicode-math",Text
"\\mittau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL TAU"}
, Record {uchar :: Char
uchar = Char
'\120592', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\upsilon"),(Text
"omlmathit",Text
"\\mathit{\\upsilon}"),(Text
"unicode-math",Text
"\\mitupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120593', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varphi"),(Text
"omlmathit",Text
"\\mathit{\\varphi}"),(Text
"unicode-math",Text
"\\mitphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL PHI"}
, Record {uchar :: Char
uchar = Char
'\120594', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\chi"),(Text
"omlmathit",Text
"\\mathit{\\chi}"),(Text
"unicode-math",Text
"\\mitchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL CHI"}
, Record {uchar :: Char
uchar = Char
'\120595', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\psi"),(Text
"omlmathit",Text
"\\mathit{\\psi}"),(Text
"unicode-math",Text
"\\mitpsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL PSI"}
, Record {uchar :: Char
uchar = Char
'\120596', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\omega"),(Text
"omlmathit",Text
"\\mathit{\\omega}"),(Text
"unicode-math",Text
"\\mitomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC SMALL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120597', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\partial"),(Text
"omlmathit",Text
"\\mathit{\\partial}"),(Text
"unicode-math",Text
"\\mitpartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL ITALIC PARTIAL DIFFERENTIAL"}
, Record {uchar :: Char
uchar = Char
'\120598', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\epsilon"),(Text
"omlmathit",Text
"\\mathit{\\epsilon}"),(Text
"unicode-math",Text
"\\mitvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC EPSILON SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120599', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\vartheta"),(Text
"omlmathit",Text
"\\mathit{\\vartheta}"),(Text
"unicode-math",Text
"\\mitvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120600', commands :: [(Text, Text)]
commands = [(Text
"amssymb",Text
"\\varkappa"),(Text
"unicode-math",Text
"\\mitvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC KAPPA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120601', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\phi"),(Text
"omlmathit",Text
"\\mathit{\\phi}"),(Text
"unicode-math",Text
"\\mitvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC PHI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120602', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varrho"),(Text
"omlmathit",Text
"\\mathit{\\varrho}"),(Text
"unicode-math",Text
"\\mitvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC RHO SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120603', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\varpi"),(Text
"omlmathit",Text
"\\mathit{\\varpi}"),(Text
"unicode-math",Text
"\\mitvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL ITALIC PI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120604', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120605', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL BETA"}
, Record {uchar :: Char
uchar = Char
'\120606', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Gamma}"),(Text
"fixmath",Text
"\\mathbold{\\Gamma}"),(Text
"unicode-math",Text
"\\mbfitGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120607', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Delta}"),(Text
"fixmath",Text
"\\mathbold{\\Delta}"),(Text
"unicode-math",Text
"\\mbfitDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120608', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120609', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120610', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL ETA"}
, Record {uchar :: Char
uchar = Char
'\120611', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Theta}"),(Text
"fixmath",Text
"\\mathbold{\\Theta}"),(Text
"unicode-math",Text
"\\mbfitTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL THETA"}
, Record {uchar :: Char
uchar = Char
'\120612', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120613', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120614', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Lambda}"),(Text
"fixmath",Text
"\\mathbold{\\Lambda}"),(Text
"unicode-math",Text
"\\mbfitLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical bold italic capital lambda"}
, Record {uchar :: Char
uchar = Char
'\120615', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL MU"}
, Record {uchar :: Char
uchar = Char
'\120616', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL NU"}
, Record {uchar :: Char
uchar = Char
'\120617', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Xi}"),(Text
"fixmath",Text
"\\mathbold{\\Xi}"),(Text
"unicode-math",Text
"\\mbfitXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL XI"}
, Record {uchar :: Char
uchar = Char
'\120618', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120619', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Pi}"),(Text
"fixmath",Text
"\\mathbold{\\Pi}"),(Text
"unicode-math",Text
"\\mbfitPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL PI"}
, Record {uchar :: Char
uchar = Char
'\120620', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL RHO"}
, Record {uchar :: Char
uchar = Char
'\120621', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120622', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Sigma}"),(Text
"fixmath",Text
"\\mathbold{\\Sigma}"),(Text
"unicode-math",Text
"\\mbfitSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120623', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL TAU"}
, Record {uchar :: Char
uchar = Char
'\120624', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Upsilon}"),(Text
"fixmath",Text
"\\mathbold{\\Upsilon}"),(Text
"unicode-math",Text
"\\mbfitUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120625', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Phi}"),(Text
"fixmath",Text
"\\mathbold{\\Phi}"),(Text
"unicode-math",Text
"\\mbfitPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL PHI"}
, Record {uchar :: Char
uchar = Char
'\120626', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL CHI"}
, Record {uchar :: Char
uchar = Char
'\120627', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Psi}"),(Text
"fixmath",Text
"\\mathbold{\\Psi}"),(Text
"unicode-math",Text
"\\mbfitPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL PSI"}
, Record {uchar :: Char
uchar = Char
'\120628', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\Omega}"),(Text
"fixmath",Text
"\\mathbold{\\Omega}"),(Text
"unicode-math",Text
"\\mbfitOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC CAPITAL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120629', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC NABLA"}
, Record {uchar :: Char
uchar = Char
'\120630', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\alpha}"),(Text
"fixmath",Text
"\\mathbold{\\alpha}"),(Text
"unicode-math",Text
"\\mbfitalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120631', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\beta}"),(Text
"fixmath",Text
"\\mathbold{\\beta}"),(Text
"unicode-math",Text
"\\mbfitbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL BETA"}
, Record {uchar :: Char
uchar = Char
'\120632', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\gamma}"),(Text
"fixmath",Text
"\\mathbold{\\gamma}"),(Text
"unicode-math",Text
"\\mbfitgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120633', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\delta}"),(Text
"fixmath",Text
"\\mathbold{\\delta}"),(Text
"unicode-math",Text
"\\mbfitdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120634', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\varepsilon}"),(Text
"fixmath",Text
"\\mathbold{\\varepsilon}"),(Text
"unicode-math",Text
"\\mbfitepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120635', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\zeta}"),(Text
"fixmath",Text
"\\mathbold{\\zeta}"),(Text
"unicode-math",Text
"\\mbfitzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120636', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\eta}"),(Text
"fixmath",Text
"\\mathbold{\\eta}"),(Text
"unicode-math",Text
"\\mbfiteta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL ETA"}
, Record {uchar :: Char
uchar = Char
'\120637', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\theta}"),(Text
"fixmath",Text
"\\mathbold{\\theta}"),(Text
"unicode-math",Text
"\\mbfittheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL THETA"}
, Record {uchar :: Char
uchar = Char
'\120638', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\iota}"),(Text
"fixmath",Text
"\\mathbold{\\iota}"),(Text
"unicode-math",Text
"\\mbfitiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120639', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\kappa}"),(Text
"fixmath",Text
"\\mathbold{\\kappa}"),(Text
"unicode-math",Text
"\\mbfitkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120640', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\lambda}"),(Text
"fixmath",Text
"\\mathbold{\\lambda}"),(Text
"unicode-math",Text
"\\mbfitlambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical bold italic small lambda"}
, Record {uchar :: Char
uchar = Char
'\120641', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\mu}"),(Text
"fixmath",Text
"\\mathbold{\\mu}"),(Text
"unicode-math",Text
"\\mbfitmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL MU"}
, Record {uchar :: Char
uchar = Char
'\120642', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\nu}"),(Text
"fixmath",Text
"\\mathbold{\\nu}"),(Text
"unicode-math",Text
"\\mbfitnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL NU"}
, Record {uchar :: Char
uchar = Char
'\120643', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\xi}"),(Text
"fixmath",Text
"\\mathbold{\\xi}"),(Text
"unicode-math",Text
"\\mbfitxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL XI"}
, Record {uchar :: Char
uchar = Char
'\120644', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120645', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\pi}"),(Text
"fixmath",Text
"\\mathbold{\\pi}"),(Text
"unicode-math",Text
"\\mbfitpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL PI"}
, Record {uchar :: Char
uchar = Char
'\120646', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\rho}"),(Text
"fixmath",Text
"\\mathbold{\\rho}"),(Text
"unicode-math",Text
"\\mbfitrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL RHO"}
, Record {uchar :: Char
uchar = Char
'\120647', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\varsigma}"),(Text
"fixmath",Text
"\\mathbold{\\varsigma}"),(Text
"unicode-math",Text
"\\mbfitvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL FINAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120648', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\sigma}"),(Text
"fixmath",Text
"\\mathbold{\\sigma}"),(Text
"unicode-math",Text
"\\mbfitsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120649', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\tau}"),(Text
"fixmath",Text
"\\mathbold{\\tau}"),(Text
"unicode-math",Text
"\\mbfittau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL TAU"}
, Record {uchar :: Char
uchar = Char
'\120650', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\upsilon}"),(Text
"fixmath",Text
"\\mathbold{\\upsilon}"),(Text
"unicode-math",Text
"\\mbfitupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120651', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\varphi}"),(Text
"fixmath",Text
"\\mathbold{\\varphi}"),(Text
"unicode-math",Text
"\\mbfitphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL PHI"}
, Record {uchar :: Char
uchar = Char
'\120652', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\chi}"),(Text
"fixmath",Text
"\\mathbold{\\chi}"),(Text
"unicode-math",Text
"\\mbfitchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL CHI"}
, Record {uchar :: Char
uchar = Char
'\120653', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\psi}"),(Text
"fixmath",Text
"\\mathbold{\\psi}"),(Text
"unicode-math",Text
"\\mbfitpsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL PSI"}
, Record {uchar :: Char
uchar = Char
'\120654', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\omega}"),(Text
"fixmath",Text
"\\mathbold{\\omega}"),(Text
"unicode-math",Text
"\\mbfitomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC SMALL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120655', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitpartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC PARTIAL DIFFERENTIAL"}
, Record {uchar :: Char
uchar = Char
'\120656', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\epsilon}"),(Text
"fixmath",Text
"\\mathbold{\\epsilon}"),(Text
"unicode-math",Text
"\\mbfitvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC EPSILON SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120657', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\vartheta}"),(Text
"fixmath",Text
"\\mathbold{\\vartheta}"),(Text
"unicode-math",Text
"\\mbfitvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120658', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC KAPPA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120659', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\phi}"),(Text
"fixmath",Text
"\\mathbold{\\phi}"),(Text
"unicode-math",Text
"\\mbfitvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC PHI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120660', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\varrho}"),(Text
"fixmath",Text
"\\mathbold{\\varrho}"),(Text
"unicode-math",Text
"\\mbfitvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC RHO SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120661', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathbfit{\\varpi}"),(Text
"fixmath",Text
"\\mathbold{\\varpi}"),(Text
"unicode-math",Text
"\\mbfitvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD ITALIC PI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120662', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120663', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL BETA"}
, Record {uchar :: Char
uchar = Char
'\120664', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Gamma}"),(Text
"unicode-math",Text
"\\mbfsansGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120665', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Delta}"),(Text
"unicode-math",Text
"\\mbfsansDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120666', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120667', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120668', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL ETA"}
, Record {uchar :: Char
uchar = Char
'\120669', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Theta}"),(Text
"unicode-math",Text
"\\mbfsansTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL THETA"}
, Record {uchar :: Char
uchar = Char
'\120670', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120671', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120672', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Lambda}"),(Text
"unicode-math",Text
"\\mbfsansLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical sans-serif bold capital lambda"}
, Record {uchar :: Char
uchar = Char
'\120673', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL MU"}
, Record {uchar :: Char
uchar = Char
'\120674', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL NU"}
, Record {uchar :: Char
uchar = Char
'\120675', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Xi}"),(Text
"unicode-math",Text
"\\mbfsansXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL XI"}
, Record {uchar :: Char
uchar = Char
'\120676', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120677', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Pi}"),(Text
"unicode-math",Text
"\\mbfsansPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL PI"}
, Record {uchar :: Char
uchar = Char
'\120678', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL RHO"}
, Record {uchar :: Char
uchar = Char
'\120679', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120680', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Sigma}"),(Text
"unicode-math",Text
"\\mbfsansSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120681', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL TAU"}
, Record {uchar :: Char
uchar = Char
'\120682', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Upsilon}"),(Text
"unicode-math",Text
"\\mbfsansUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120683', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Phi}"),(Text
"unicode-math",Text
"\\mbfsansPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL PHI"}
, Record {uchar :: Char
uchar = Char
'\120684', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL CHI"}
, Record {uchar :: Char
uchar = Char
'\120685', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Psi}"),(Text
"unicode-math",Text
"\\mbfsansPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL PSI"}
, Record {uchar :: Char
uchar = Char
'\120686', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{\\Omega}"),(Text
"unicode-math",Text
"\\mbfsansOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD CAPITAL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120687', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD NABLA"}
, Record {uchar :: Char
uchar = Char
'\120688', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\alpha}"),(Text
"unicode-math",Text
"\\mbfsansalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120689', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\beta}"),(Text
"unicode-math",Text
"\\mbfsansbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL BETA"}
, Record {uchar :: Char
uchar = Char
'\120690', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\gamma}"),(Text
"unicode-math",Text
"\\mbfsansgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120691', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\delta}"),(Text
"unicode-math",Text
"\\mbfsansdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120692', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\varepsilon}"),(Text
"unicode-math",Text
"\\mbfsansepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120693', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\zeta}"),(Text
"unicode-math",Text
"\\mbfsanszeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120694', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\eta}"),(Text
"unicode-math",Text
"\\mbfsanseta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL ETA"}
, Record {uchar :: Char
uchar = Char
'\120695', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\theta}"),(Text
"unicode-math",Text
"\\mbfsanstheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL THETA"}
, Record {uchar :: Char
uchar = Char
'\120696', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\iota}"),(Text
"unicode-math",Text
"\\mbfsansiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120697', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\kappa}"),(Text
"unicode-math",Text
"\\mbfsanskappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120698', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\lambda}"),(Text
"unicode-math",Text
"\\mbfsanslambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical sans-serif bold small lambda"}
, Record {uchar :: Char
uchar = Char
'\120699', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\mu}"),(Text
"unicode-math",Text
"\\mbfsansmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL MU"}
, Record {uchar :: Char
uchar = Char
'\120700', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\nu}"),(Text
"unicode-math",Text
"\\mbfsansnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL NU"}
, Record {uchar :: Char
uchar = Char
'\120701', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\xi}"),(Text
"unicode-math",Text
"\\mbfsansxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL XI"}
, Record {uchar :: Char
uchar = Char
'\120702', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120703', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\pi}"),(Text
"unicode-math",Text
"\\mbfsanspi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL PI"}
, Record {uchar :: Char
uchar = Char
'\120704', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\rho}"),(Text
"unicode-math",Text
"\\mbfsansrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL RHO"}
, Record {uchar :: Char
uchar = Char
'\120705', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\varsigma}"),(Text
"unicode-math",Text
"\\mbfsansvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL FINAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120706', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\sigma}"),(Text
"unicode-math",Text
"\\mbfsanssigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120707', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\tau}"),(Text
"unicode-math",Text
"\\mbfsanstau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL TAU"}
, Record {uchar :: Char
uchar = Char
'\120708', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\upsilon}"),(Text
"unicode-math",Text
"\\mbfsansupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120709', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\varphi}"),(Text
"unicode-math",Text
"\\mbfsansphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL PHI"}
, Record {uchar :: Char
uchar = Char
'\120710', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\chi}"),(Text
"unicode-math",Text
"\\mbfsanschi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL CHI"}
, Record {uchar :: Char
uchar = Char
'\120711', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\psi}"),(Text
"unicode-math",Text
"\\mbfsanspsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL PSI"}
, Record {uchar :: Char
uchar = Char
'\120712', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\omega}"),(Text
"unicode-math",Text
"\\mbfsansomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD SMALL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120713', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsanspartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD PARTIAL DIFFERENTIAL"}
, Record {uchar :: Char
uchar = Char
'\120714', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\epsilon}"),(Text
"unicode-math",Text
"\\mbfsansvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD EPSILON SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120715', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\vartheta}"),(Text
"unicode-math",Text
"\\mbfsansvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120716', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfsansvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD KAPPA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120717', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\phi}"),(Text
"unicode-math",Text
"\\mbfsansvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD PHI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120718', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\varrho}"),(Text
"unicode-math",Text
"\\mbfsansvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD RHO SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120719', commands :: [(Text, Text)]
commands = [(Text
"omlmathsfbf",Text
"\\mathsfbf{\\varpi}"),(Text
"unicode-math",Text
"\\mbfsansvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD PI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120720', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120721', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL BETA"}
, Record {uchar :: Char
uchar = Char
'\120722', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Gamma}"),(Text
"unicode-math",Text
"\\mbfitsansGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120723', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Delta}"),(Text
"unicode-math",Text
"\\mbfitsansDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120724', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120725', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120726', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL ETA"}
, Record {uchar :: Char
uchar = Char
'\120727', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Theta}"),(Text
"unicode-math",Text
"\\mbfitsansTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL THETA"}
, Record {uchar :: Char
uchar = Char
'\120728', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120729', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120730', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Lambda}"),(Text
"unicode-math",Text
"\\mbfitsansLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical sans-serif bold italic capital lambda"}
, Record {uchar :: Char
uchar = Char
'\120731', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL MU"}
, Record {uchar :: Char
uchar = Char
'\120732', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL NU"}
, Record {uchar :: Char
uchar = Char
'\120733', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Xi}"),(Text
"unicode-math",Text
"\\mbfitsansXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL XI"}
, Record {uchar :: Char
uchar = Char
'\120734', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120735', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Pi}"),(Text
"unicode-math",Text
"\\mbfitsansPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL PI"}
, Record {uchar :: Char
uchar = Char
'\120736', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL RHO"}
, Record {uchar :: Char
uchar = Char
'\120737', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120738', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Sigma}"),(Text
"unicode-math",Text
"\\mbfitsansSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120739', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL TAU"}
, Record {uchar :: Char
uchar = Char
'\120740', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Upsilon}"),(Text
"unicode-math",Text
"\\mbfitsansUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120741', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Phi}"),(Text
"unicode-math",Text
"\\mbfitsansPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL PHI"}
, Record {uchar :: Char
uchar = Char
'\120742', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL CHI"}
, Record {uchar :: Char
uchar = Char
'\120743', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Psi}"),(Text
"unicode-math",Text
"\\mbfitsansPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL PSI"}
, Record {uchar :: Char
uchar = Char
'\120744', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\Omega}"),(Text
"unicode-math",Text
"\\mbfitsansOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120745', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC NABLA"}
, Record {uchar :: Char
uchar = Char
'\120746', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\alpha}"),(Text
"unicode-math",Text
"\\mbfitsansalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL ALPHA"}
, Record {uchar :: Char
uchar = Char
'\120747', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\beta}"),(Text
"unicode-math",Text
"\\mbfitsansbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL BETA"}
, Record {uchar :: Char
uchar = Char
'\120748', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\gamma}"),(Text
"unicode-math",Text
"\\mbfitsansgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL GAMMA"}
, Record {uchar :: Char
uchar = Char
'\120749', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\delta}"),(Text
"unicode-math",Text
"\\mbfitsansdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL DELTA"}
, Record {uchar :: Char
uchar = Char
'\120750', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\varepsilon}"),(Text
"unicode-math",Text
"\\mbfitsansepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL EPSILON"}
, Record {uchar :: Char
uchar = Char
'\120751', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\zeta}"),(Text
"unicode-math",Text
"\\mbfitsanszeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL ZETA"}
, Record {uchar :: Char
uchar = Char
'\120752', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\eta}"),(Text
"unicode-math",Text
"\\mbfitsanseta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL ETA"}
, Record {uchar :: Char
uchar = Char
'\120753', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\theta}"),(Text
"unicode-math",Text
"\\mbfitsanstheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL THETA"}
, Record {uchar :: Char
uchar = Char
'\120754', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\iota}"),(Text
"unicode-math",Text
"\\mbfitsansiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL IOTA"}
, Record {uchar :: Char
uchar = Char
'\120755', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\kappa}"),(Text
"unicode-math",Text
"\\mbfitsanskappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL KAPPA"}
, Record {uchar :: Char
uchar = Char
'\120756', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\lambda}"),(Text
"unicode-math",Text
"\\mbfitsanslambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"mathematical sans-serif bold italic small lambda"}
, Record {uchar :: Char
uchar = Char
'\120757', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\mu}"),(Text
"unicode-math",Text
"\\mbfitsansmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL MU"}
, Record {uchar :: Char
uchar = Char
'\120758', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\nu}"),(Text
"unicode-math",Text
"\\mbfitsansnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL NU"}
, Record {uchar :: Char
uchar = Char
'\120759', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\xi}"),(Text
"unicode-math",Text
"\\mbfitsansxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL XI"}
, Record {uchar :: Char
uchar = Char
'\120760', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL OMICRON"}
, Record {uchar :: Char
uchar = Char
'\120761', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\pi}"),(Text
"unicode-math",Text
"\\mbfitsanspi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL PI"}
, Record {uchar :: Char
uchar = Char
'\120762', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\rho}"),(Text
"unicode-math",Text
"\\mbfitsansrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL RHO"}
, Record {uchar :: Char
uchar = Char
'\120763', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\varsigma}"),(Text
"unicode-math",Text
"\\mbfitsansvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL FINAL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120764', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\sigma}"),(Text
"unicode-math",Text
"\\mbfitsanssigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL SIGMA"}
, Record {uchar :: Char
uchar = Char
'\120765', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\tau}"),(Text
"unicode-math",Text
"\\mbfitsanstau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL TAU"}
, Record {uchar :: Char
uchar = Char
'\120766', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\upsilon}"),(Text
"unicode-math",Text
"\\mbfitsansupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL UPSILON"}
, Record {uchar :: Char
uchar = Char
'\120767', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\varphi}"),(Text
"unicode-math",Text
"\\mbfitsansphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL PHI"}
, Record {uchar :: Char
uchar = Char
'\120768', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\chi}"),(Text
"unicode-math",Text
"\\mbfitsanschi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL CHI"}
, Record {uchar :: Char
uchar = Char
'\120769', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\psi}"),(Text
"unicode-math",Text
"\\mbfitsanspsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL PSI"}
, Record {uchar :: Char
uchar = Char
'\120770', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\omega}"),(Text
"unicode-math",Text
"\\mbfitsansomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL OMEGA"}
, Record {uchar :: Char
uchar = Char
'\120771', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsanspartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC PARTIAL DIFFERENTIAL"}
, Record {uchar :: Char
uchar = Char
'\120772', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\epsilon}"),(Text
"unicode-math",Text
"\\mbfitsansvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC EPSILON SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120773', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\vartheta}"),(Text
"unicode-math",Text
"\\mbfitsansvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC THETA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120774', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfitsansvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC KAPPA SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120775', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\phi}"),(Text
"unicode-math",Text
"\\mbfitsansvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC PHI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120776', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\varrho}"),(Text
"unicode-math",Text
"\\mbfitsansvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC RHO SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120777', commands :: [(Text, Text)]
commands = [(Text
"isomath",Text
"\\mathsfbfit{\\varpi}"),(Text
"unicode-math",Text
"\\mbfitsansvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL SANS-SERIF BOLD ITALIC PI SYMBOL"}
, Record {uchar :: Char
uchar = Char
'\120778', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfDigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD CAPITAL DIGAMMA"}
, Record {uchar :: Char
uchar = Char
'\120779', commands :: [(Text, Text)]
commands = [(Text
"unicode-math",Text
"\\mbfdigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = Text
"MATHEMATICAL BOLD SMALL DIGAMMA"}
, Record {uchar :: Char
uchar = Char
'\120782', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{0}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 0"}
, Record {uchar :: Char
uchar = Char
'\120783', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{1}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 1"}
, Record {uchar :: Char
uchar = Char
'\120784', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{2}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 2"}
, Record {uchar :: Char
uchar = Char
'\120785', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{3}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 3"}
, Record {uchar :: Char
uchar = Char
'\120786', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{4}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 4"}
, Record {uchar :: Char
uchar = Char
'\120787', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{5}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 5"}
, Record {uchar :: Char
uchar = Char
'\120788', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{6}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 6"}
, Record {uchar :: Char
uchar = Char
'\120789', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{7}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 7"}
, Record {uchar :: Char
uchar = Char
'\120790', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{8}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 8"}
, Record {uchar :: Char
uchar = Char
'\120791', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathbf{9}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical bold digit 9"}
, Record {uchar :: Char
uchar = Char
'\120792', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{0}"),(Text
"unicode-math",Text
"\\Bbbzero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 0"}
, Record {uchar :: Char
uchar = Char
'\120793', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{1}"),(Text
"fourier",Text
"\\mathbb{1}"),(Text
"dsfont",Text
"\\mathds{1}"),(Text
"unicode-math",Text
"\\Bbbone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 1"}
, Record {uchar :: Char
uchar = Char
'\120794', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{2}"),(Text
"unicode-math",Text
"\\Bbbtwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 2"}
, Record {uchar :: Char
uchar = Char
'\120795', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{3}"),(Text
"unicode-math",Text
"\\Bbbthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 3"}
, Record {uchar :: Char
uchar = Char
'\120796', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{4}"),(Text
"unicode-math",Text
"\\Bbbfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 4"}
, Record {uchar :: Char
uchar = Char
'\120797', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{5}"),(Text
"unicode-math",Text
"\\Bbbfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 5"}
, Record {uchar :: Char
uchar = Char
'\120798', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{6}"),(Text
"unicode-math",Text
"\\Bbbsix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 6"}
, Record {uchar :: Char
uchar = Char
'\120799', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{7}"),(Text
"unicode-math",Text
"\\Bbbseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 7"}
, Record {uchar :: Char
uchar = Char
'\120800', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{8}"),(Text
"unicode-math",Text
"\\Bbbeight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 8"}
, Record {uchar :: Char
uchar = Char
'\120801', commands :: [(Text, Text)]
commands = [(Text
"bbold",Text
"\\mathbb{9}"),(Text
"unicode-math",Text
"\\Bbbnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical double-struck digit 9"}
, Record {uchar :: Char
uchar = Char
'\120802', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{0}"),(Text
"unicode-math",Text
"\\msanszero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 0"}
, Record {uchar :: Char
uchar = Char
'\120803', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{1}"),(Text
"unicode-math",Text
"\\msansone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 1"}
, Record {uchar :: Char
uchar = Char
'\120804', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{2}"),(Text
"unicode-math",Text
"\\msanstwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 2"}
, Record {uchar :: Char
uchar = Char
'\120805', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{3}"),(Text
"unicode-math",Text
"\\msansthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 3"}
, Record {uchar :: Char
uchar = Char
'\120806', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{4}"),(Text
"unicode-math",Text
"\\msansfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 4"}
, Record {uchar :: Char
uchar = Char
'\120807', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{5}"),(Text
"unicode-math",Text
"\\msansfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 5"}
, Record {uchar :: Char
uchar = Char
'\120808', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{6}"),(Text
"unicode-math",Text
"\\msanssix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 6"}
, Record {uchar :: Char
uchar = Char
'\120809', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{7}"),(Text
"unicode-math",Text
"\\msansseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 7"}
, Record {uchar :: Char
uchar = Char
'\120810', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{8}"),(Text
"unicode-math",Text
"\\msanseight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 8"}
, Record {uchar :: Char
uchar = Char
'\120811', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathsf{9}"),(Text
"unicode-math",Text
"\\msansnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif digit 9"}
, Record {uchar :: Char
uchar = Char
'\120812', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{0}"),(Text
"unicode-math",Text
"\\mbfsanszero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 0"}
, Record {uchar :: Char
uchar = Char
'\120813', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{1}"),(Text
"unicode-math",Text
"\\mbfsansone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 1"}
, Record {uchar :: Char
uchar = Char
'\120814', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{2}"),(Text
"unicode-math",Text
"\\mbfsanstwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 2"}
, Record {uchar :: Char
uchar = Char
'\120815', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{3}"),(Text
"unicode-math",Text
"\\mbfsansthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 3"}
, Record {uchar :: Char
uchar = Char
'\120816', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{4}"),(Text
"unicode-math",Text
"\\mbfsansfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 4"}
, Record {uchar :: Char
uchar = Char
'\120817', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{5}"),(Text
"unicode-math",Text
"\\mbfsansfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 5"}
, Record {uchar :: Char
uchar = Char
'\120818', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{6}"),(Text
"unicode-math",Text
"\\mbfsanssix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 6"}
, Record {uchar :: Char
uchar = Char
'\120819', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{7}"),(Text
"unicode-math",Text
"\\mbfsansseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 7"}
, Record {uchar :: Char
uchar = Char
'\120820', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{8}"),(Text
"unicode-math",Text
"\\mbfsanseight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 8"}
, Record {uchar :: Char
uchar = Char
'\120821', commands :: [(Text, Text)]
commands = [(Text
"mathsfbf",Text
"\\mathsfbf{9}"),(Text
"unicode-math",Text
"\\mbfsansnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical sans-serif bold digit 9"}
, Record {uchar :: Char
uchar = Char
'\120822', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{0}"),(Text
"unicode-math",Text
"\\mttzero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 0"}
, Record {uchar :: Char
uchar = Char
'\120823', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{1}"),(Text
"unicode-math",Text
"\\mttone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 1"}
, Record {uchar :: Char
uchar = Char
'\120824', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{2}"),(Text
"unicode-math",Text
"\\mtttwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 2"}
, Record {uchar :: Char
uchar = Char
'\120825', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{3}"),(Text
"unicode-math",Text
"\\mttthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 3"}
, Record {uchar :: Char
uchar = Char
'\120826', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{4}"),(Text
"unicode-math",Text
"\\mttfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 4"}
, Record {uchar :: Char
uchar = Char
'\120827', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{5}"),(Text
"unicode-math",Text
"\\mttfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 5"}
, Record {uchar :: Char
uchar = Char
'\120828', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{6}"),(Text
"unicode-math",Text
"\\mttsix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 6"}
, Record {uchar :: Char
uchar = Char
'\120829', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{7}"),(Text
"unicode-math",Text
"\\mttseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 7"}
, Record {uchar :: Char
uchar = Char
'\120830', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{8}"),(Text
"unicode-math",Text
"\\mtteight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 8"}
, Record {uchar :: Char
uchar = Char
'\120831', commands :: [(Text, Text)]
commands = [(Text
"base",Text
"\\mathtt{9}"),(Text
"unicode-math",Text
"\\mttnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = Text
"mathematical monospace digit 9"}]