{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.TeXMath.Unicode.ToTeX ( getTeXMath
, getSymbolType
, 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 s :: Text
s e :: 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 e :: Env
e c :: 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 (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 _ '\65024' = [TeX] -> Maybe [TeX]
forall a. a -> Maybe a
Just []
charToLaTeXString environment :: Env
environment c :: 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 cs :: Text
cs = case Text -> Maybe (Char, Text)
T.uncons Text
cs of
Just (x :: Char
x, xs :: Text
xs) -> if Text -> Bool
T.null Text
xs then [Char -> TeX
Token Char
x] else [Text -> TeX
Literal Text
cs]
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 "base" [(Text, Text)]
cmds Maybe Text -> Maybe Text -> Maybe Text
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 (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 (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
env c :: Char
c = do
(ttype :: TextType
ttype, v :: Char
v) <- Char -> Maybe (TextType, Char)
fromUnicodeChar Char
c
[TeX] -> Maybe [TeX]
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 r :: Record
r = (Record -> Char
uchar Record
r, Record
r)
getSymbolType :: Char -> TeXSymbolType
getSymbolType :: Char -> TeXSymbolType
getSymbolType c :: 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)
records :: [Record]
records :: [Record]
records =
[ Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '!', commands :: [(Text, Text)]
commands = [("base","!"),("unicode-math","\\exclam")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = "EXCLAMATION MARK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '#', commands :: [(Text, Text)]
commands = [("base","\\#"),("oz","\\#"),("unicode-math","\\octothorpe")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NUMBER SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '$', commands :: [(Text, Text)]
commands = [("base","\\$"),("base","\\mathdollar"),("unicode-math","\\mathdollar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOLLAR SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '%', commands :: [(Text, Text)]
commands = [("base","\\%"),("unicode-math","\\percent")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PERCENT SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '&', commands :: [(Text, Text)]
commands = [("base","\\&"),("stmaryrd","\\binampersand"),("unicode-math","\\ampersand")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = ""}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '(', commands :: [(Text, Text)]
commands = [("base","("),("unicode-math","\\lparen")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT PARENTHESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = ')', commands :: [(Text, Text)]
commands = [("base",")"),("unicode-math","\\rparen")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT PARENTHESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '*', commands :: [(Text, Text)]
commands = [("base","*"),("base","\\ast")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "(high) ASTERISK, star"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '+', commands :: [(Text, Text)]
commands = [("base","+"),("unicode-math","\\plus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = ',', commands :: [(Text, Text)]
commands = [("base",","),("unicode-math","\\comma")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = "COMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '-', commands :: [(Text, Text)]
commands = [("base","-")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "t -, HYPHEN-MINUS (deprecated for math)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '.', commands :: [(Text, Text)]
commands = [("base","."),("unicode-math","\\period")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "FULL STOP, period"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '/', commands :: [(Text, Text)]
commands = [("base","/"),("base","\\slash"),("unicode-math","\\mathslash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SOLIDUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '0', commands :: [(Text, Text)]
commands = [("base","0")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT ZERO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '1', commands :: [(Text, Text)]
commands = [("base","1")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT ONE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '2', commands :: [(Text, Text)]
commands = [("base","2")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT TWO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '3', commands :: [(Text, Text)]
commands = [("base","3")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT THREE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '4', commands :: [(Text, Text)]
commands = [("base","4")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT FOUR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '5', commands :: [(Text, Text)]
commands = [("base","5")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT FIVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '6', commands :: [(Text, Text)]
commands = [("base","6")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT SIX"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '7', commands :: [(Text, Text)]
commands = [("base","7")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT SEVEN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '8', commands :: [(Text, Text)]
commands = [("base","8")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT EIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '9', commands :: [(Text, Text)]
commands = [("base","9")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIGIT NINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = ':', commands :: [(Text, Text)]
commands = [("base",":"),("literal","\\colon"),("unicode-math","\\mathcolon")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = "COLON (not ratio)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = ';', commands :: [(Text, Text)]
commands = [("base",";"),("unicode-math","\\semicolon")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = "SEMICOLON p:"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '<', commands :: [(Text, Text)]
commands = [("base","<"),("unicode-math","\\less")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN SIGN r:"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '=', commands :: [(Text, Text)]
commands = [("base","="),("unicode-math","\\equal")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN r:"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '>', commands :: [(Text, Text)]
commands = [("base",">"),("unicode-math","\\greater")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN SIGN r:"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '?', commands :: [(Text, Text)]
commands = [("base","?"),("unicode-math","\\question")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "QUESTION MARK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '@', commands :: [(Text, Text)]
commands = [("base","@"),("unicode-math","\\atsign")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "at"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'A', commands :: [(Text, Text)]
commands = [("base","A"),("base","\\mathrm{A}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'B', commands :: [(Text, Text)]
commands = [("base","B"),("base","\\mathrm{B}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'C', commands :: [(Text, Text)]
commands = [("base","C"),("base","\\mathrm{C}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'D', commands :: [(Text, Text)]
commands = [("base","D"),("base","\\mathrm{D}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'E', commands :: [(Text, Text)]
commands = [("base","E"),("base","\\mathrm{E}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'F', commands :: [(Text, Text)]
commands = [("base","F"),("base","\\mathrm{F}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'G', commands :: [(Text, Text)]
commands = [("base","G"),("base","\\mathrm{G}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'H', commands :: [(Text, Text)]
commands = [("base","H"),("base","\\mathrm{H}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'I', commands :: [(Text, Text)]
commands = [("base","I"),("base","\\mathrm{I}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'J', commands :: [(Text, Text)]
commands = [("base","J"),("base","\\mathrm{J}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'K', commands :: [(Text, Text)]
commands = [("base","K"),("base","\\mathrm{K}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'L', commands :: [(Text, Text)]
commands = [("base","L"),("base","\\mathrm{L}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'M', commands :: [(Text, Text)]
commands = [("base","M"),("base","\\mathrm{M}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'N', commands :: [(Text, Text)]
commands = [("base","N"),("base","\\mathrm{N}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'O', commands :: [(Text, Text)]
commands = [("base","O"),("base","\\mathrm{O}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'P', commands :: [(Text, Text)]
commands = [("base","P"),("base","\\mathrm{P}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'Q', commands :: [(Text, Text)]
commands = [("base","Q"),("base","\\mathrm{Q}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'R', commands :: [(Text, Text)]
commands = [("base","R"),("base","\\mathrm{R}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'S', commands :: [(Text, Text)]
commands = [("base","S"),("base","\\mathrm{S}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'T', commands :: [(Text, Text)]
commands = [("base","T"),("base","\\mathrm{T}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'U', commands :: [(Text, Text)]
commands = [("base","U"),("base","\\mathrm{U}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'V', commands :: [(Text, Text)]
commands = [("base","V"),("base","\\mathrm{V}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'W', commands :: [(Text, Text)]
commands = [("base","W"),("base","\\mathrm{W}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'X', commands :: [(Text, Text)]
commands = [("base","X"),("base","\\mathrm{X}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'Y', commands :: [(Text, Text)]
commands = [("base","Y"),("base","\\mathrm{Y}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'Z', commands :: [(Text, Text)]
commands = [("base","Z"),("base","\\mathrm{Z}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN CAPITAL LETTER Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '[', commands :: [(Text, Text)]
commands = [("base","\\lbrack"),("unicode-math","\\lbrack")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT SQUARE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\\', commands :: [(Text, Text)]
commands = [("base","\\backslash"),("unicode-math","\\backslash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "REVERSE SOLIDUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = ']', commands :: [(Text, Text)]
commands = [("base","\\rbrack"),("unicode-math","\\rbrack")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT SQUARE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '^', commands :: [(Text, Text)]
commands = [("base","\\hat{}"),("unicode-math","\\sphat")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "amsxtra^CIRCUMFLEX ACCENT, TeX superscript operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '_', commands :: [(Text, Text)]
commands = [("base","\\_")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOW LINE, TeX subscript operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '`', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "grave, alias for 0300"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'a', commands :: [(Text, Text)]
commands = [("base","a"),("base","\\mathrm{a}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'b', commands :: [(Text, Text)]
commands = [("base","b"),("base","\\mathrm{b}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'c', commands :: [(Text, Text)]
commands = [("base","c"),("base","\\mathrm{c}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'd', commands :: [(Text, Text)]
commands = [("base","d"),("base","\\mathrm{d}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'e', commands :: [(Text, Text)]
commands = [("base","e"),("base","\\mathrm{e}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'f', commands :: [(Text, Text)]
commands = [("base","f"),("base","\\mathrm{f}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'g', commands :: [(Text, Text)]
commands = [("base","g"),("base","\\mathrm{g}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'h', commands :: [(Text, Text)]
commands = [("base","h"),("base","\\mathrm{h}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'i', commands :: [(Text, Text)]
commands = [("base","i"),("base","\\mathrm{i}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'j', commands :: [(Text, Text)]
commands = [("base","j"),("base","\\mathrm{j}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'k', commands :: [(Text, Text)]
commands = [("base","k"),("base","\\mathrm{k}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'l', commands :: [(Text, Text)]
commands = [("base","l"),("base","\\mathrm{l}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'm', commands :: [(Text, Text)]
commands = [("base","m"),("base","\\mathrm{m}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'n', commands :: [(Text, Text)]
commands = [("base","n"),("base","\\mathrm{n}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'o', commands :: [(Text, Text)]
commands = [("base","o"),("base","\\mathrm{o}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'p', commands :: [(Text, Text)]
commands = [("base","p"),("base","\\mathrm{p}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'q', commands :: [(Text, Text)]
commands = [("base","q"),("base","\\mathrm{q}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'r', commands :: [(Text, Text)]
commands = [("base","r"),("base","\\mathrm{r}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 's', commands :: [(Text, Text)]
commands = [("base","s"),("base","\\mathrm{s}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 't', commands :: [(Text, Text)]
commands = [("base","t"),("base","\\mathrm{t}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'u', commands :: [(Text, Text)]
commands = [("base","u"),("base","\\mathrm{u}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'v', commands :: [(Text, Text)]
commands = [("base","v"),("base","\\mathrm{v}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'w', commands :: [(Text, Text)]
commands = [("base","w"),("base","\\mathrm{w}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'x', commands :: [(Text, Text)]
commands = [("base","x"),("base","\\mathrm{x}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'y', commands :: [(Text, Text)]
commands = [("base","y"),("base","\\mathrm{y}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = 'z', commands :: [(Text, Text)]
commands = [("base","z"),("base","\\mathrm{z}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "LATIN SMALL LETTER Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '{', commands :: [(Text, Text)]
commands = [("base","\\{"),("base","\\lbrace"),("unicode-math","\\lbrace")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT CURLY BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '|', commands :: [(Text, Text)]
commands = [("base","|"),("base","\\vert"),("unicode-math","\\vert")], category :: TeXSymbolType
category = TeXSymbolType
Fence, comments :: Text
comments = "vertical bar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '}', commands :: [(Text, Text)]
commands = [("base","\\}"),("base","\\rbrace"),("unicode-math","\\rbrace")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT CURLY BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '~', commands :: [(Text, Text)]
commands = [("amsxtra","\\sptilde"),("base","\\sim")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TILDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\160', commands :: [(Text, Text)]
commands = [("base","~")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "nbsp"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\161', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "iexcl"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\162', commands :: [(Text, Text)]
commands = [("wasysym","\\cent"),("txfonts","\\mathcent")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "cent"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\163', commands :: [(Text, Text)]
commands = [("base","\\pounds"),("txfonts","\\mathsterling"),("unicode-math","\\sterling")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "POUND SIGN, fourier prints a dollar sign"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\164', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "t \\currency (wasysym), curren"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\165', commands :: [(Text, Text)]
commands = [("amsfonts","\\yen"),("unicode-math","\\yen")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "YEN SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\166', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "brvbar (vertical)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\167', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "sect"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\168', commands :: [(Text, Text)]
commands = [("amsxtra","\\spddot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "Dot /die, alias for 0308"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\172', commands :: [(Text, Text)]
commands = [("base","\\neg"),("base","\\lnot"),("unicode-math","\\neg")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NOT SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\174', commands :: [(Text, Text)]
commands = [("amsfonts","\\circledR")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "REGISTERED SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\175', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "macr, alias for 0304"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\176', commands :: [(Text, Text)]
commands = [("base","{^\\circ}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "deg"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\177', commands :: [(Text, Text)]
commands = [("base","\\pm"),("unicode-math","\\pm")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "plus-or-minus sign"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\178', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "sup2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\179', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "sup3"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\180', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "acute, alias for 0301"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\181', commands :: [(Text, Text)]
commands = [("wrisym","\\Micro"),("mathcomp","\\tcmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "t \\textmu (textcomp), # \\mathrm{\\mu} (omlmathrm), # \\muup (kpfonts mathdesign), MICRO SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\182', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "para (paragraph sign, pilcrow)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\183', commands :: [(Text, Text)]
commands = [("base","\\cdot"),("unicode-math","\\cdotp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "x \\centerdot, b: MIDDLE DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\185', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "sup1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\188', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "frac14"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\189', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "frac12"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\190', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "frac34"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\191', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "iquest"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\215', commands :: [(Text, Text)]
commands = [("base","\\times"),("unicode-math","\\times")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTIPLICATION SIGN, z notation Cartesian product"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\240', commands :: [(Text, Text)]
commands = [("amssymb","\\eth"),("arevmath","\\eth"),("unicode-math","\\matheth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "eth"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\247', commands :: [(Text, Text)]
commands = [("base","\\div"),("unicode-math","\\div")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "divide sign"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\305', commands :: [(Text, Text)]
commands = [("base","\\imath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "imath"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\437', commands :: [(Text, Text)]
commands = [("unicode-math","\\Zbar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "impedance"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\567', commands :: [(Text, Text)]
commands = [("base","\\jmath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "jmath"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\710', commands :: [(Text, Text)]
commands = [("base","\\hat{}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "circ, alias for 0302"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\711', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "CARON, alias for 030C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\728', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BREVE, alias for 0306"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\729', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "dot, alias for 0307"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\730', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ring, alias for 030A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\732', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "tilde, alias for 0303"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\768', commands :: [(Text, Text)]
commands = [("base","\\grave"),("unicode-math","\\grave")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "grave accent"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\769', commands :: [(Text, Text)]
commands = [("base","\\acute"),("unicode-math","\\acute")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "acute accent"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\770', commands :: [(Text, Text)]
commands = [("base","\\hat"),("amssymb","\\widehat"),("unicode-math","\\hat")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "circumflex accent"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\771', commands :: [(Text, Text)]
commands = [("base","\\tilde"),("yhmath, fourier","\\widetilde"),("unicode-math","\\tilde")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "tilde"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\772', commands :: [(Text, Text)]
commands = [("base","\\bar"),("unicode-math","\\bar")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "macron"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\773', commands :: [(Text, Text)]
commands = [("base","\\overline"),("unicode-math","\\overbar")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "overbar embellishment"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\774', commands :: [(Text, Text)]
commands = [("base","\\breve"),("unicode-math","\\breve")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "breve"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\775', commands :: [(Text, Text)]
commands = [("base","\\dot"),("wrisym","\\Dot"),("unicode-math","\\dot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "dot above"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\776', commands :: [(Text, Text)]
commands = [("base","\\ddot"),("wrisym","\\DDot"),("unicode-math","\\ddot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "dieresis"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\777', commands :: [(Text, Text)]
commands = [("unicode-math","\\ovhook")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING HOOK ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\778', commands :: [(Text, Text)]
commands = [("amssymb","\\mathring"),("yhmath","\\ring"),("unicode-math","\\ocirc")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "ring"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\780', commands :: [(Text, Text)]
commands = [("base","\\check"),("unicode-math","\\check")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "caron"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\784', commands :: [(Text, Text)]
commands = [("unicode-math","\\candra")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "candrabindu (non-spacing)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\785', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING INVERTED BREVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\786', commands :: [(Text, Text)]
commands = [("unicode-math","\\oturnedcomma")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING TURNED COMMA ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\789', commands :: [(Text, Text)]
commands = [("unicode-math","\\ocommatopright")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING COMMA ABOVE RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\794', commands :: [(Text, Text)]
commands = [("unicode-math","\\droang")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "left angle above (non-spacing)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\803', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING DOT BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\812', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING CARON BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\813', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING CIRCUMFLEX ACCENT BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\814', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING BREVE BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\815', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING INVERTED BREVE BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\816', commands :: [(Text, Text)]
commands = [("undertilde","\\utilde"),("unicode-math","\\wideutilde")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "under tilde accent (multiple characters and non-spacing)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\817', commands :: [(Text, Text)]
commands = [("base","\\underbar"),("unicode-math","\\underbar")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING MACRON BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\818', commands :: [(Text, Text)]
commands = [("base","\\underline")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LOW LINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\819', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "2lowbar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\824', commands :: [(Text, Text)]
commands = [("base","\\not"),("unicode-math","\\not")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LONG SOLIDUS OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\826', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING INVERTED BRIDGE BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\831', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING DOUBLE OVERLINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\838', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING BRIDGE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\913', commands :: [(Text, Text)]
commands = [("unicode-math","\\upAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital alpha, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\914', commands :: [(Text, Text)]
commands = [("unicode-math","\\upBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital beta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\915', commands :: [(Text, Text)]
commands = [("base","\\Gamma"),("-slantedGreek","\\Gamma"),("unicode-math","\\upGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Gamma}, capital gamma, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\916', commands :: [(Text, Text)]
commands = [("base","\\Delta"),("-slantedGreek","\\Delta"),("unicode-math","\\upDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Delta}, capital delta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\917', commands :: [(Text, Text)]
commands = [("unicode-math","\\upEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital epsilon, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\918', commands :: [(Text, Text)]
commands = [("unicode-math","\\upZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital zeta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\919', commands :: [(Text, Text)]
commands = [("unicode-math","\\upEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital eta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\920', commands :: [(Text, Text)]
commands = [("base","\\Theta"),("-slantedGreek","\\Theta"),("unicode-math","\\upTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Theta}, capital theta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\921', commands :: [(Text, Text)]
commands = [("unicode-math","\\upIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital iota, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\922', commands :: [(Text, Text)]
commands = [("unicode-math","\\upKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital kappa, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\923', commands :: [(Text, Text)]
commands = [("base","\\Lambda"),("-slantedGreek","\\Lambda"),("unicode-math","\\upLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Lambda}, capital lambda, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\924', commands :: [(Text, Text)]
commands = [("unicode-math","\\upMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital mu, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\925', commands :: [(Text, Text)]
commands = [("unicode-math","\\upNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital nu, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\926', commands :: [(Text, Text)]
commands = [("base","\\Xi"),("-slantedGreek","\\Xi"),("unicode-math","\\upXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Xi}, capital xi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\927', commands :: [(Text, Text)]
commands = [("unicode-math","\\upOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital omicron, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\928', commands :: [(Text, Text)]
commands = [("base","\\Pi"),("-slantedGreek","\\Pi"),("unicode-math","\\upPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Pi}, capital pi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\929', commands :: [(Text, Text)]
commands = [("unicode-math","\\upRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital rho, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\931', commands :: [(Text, Text)]
commands = [("base","\\Sigma"),("-slantedGreek","\\Sigma"),("unicode-math","\\upSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Sigma}, capital sigma, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\932', commands :: [(Text, Text)]
commands = [("unicode-math","\\upTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital tau, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\933', commands :: [(Text, Text)]
commands = [("base","\\Upsilon"),("-slantedGreek","\\Upsilon"),("unicode-math","\\upUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Upsilon}, capital upsilon, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\934', commands :: [(Text, Text)]
commands = [("base","\\Phi"),("-slantedGreek","\\Phi"),("unicode-math","\\upPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Phi}, capital phi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\935', commands :: [(Text, Text)]
commands = [("unicode-math","\\upChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital chi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\936', commands :: [(Text, Text)]
commands = [("base","\\Psi"),("-slantedGreek","\\Psi"),("unicode-math","\\upPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Psi}, capital psi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\937', commands :: [(Text, Text)]
commands = [("base","\\Omega"),("-slantedGreek","\\Omega"),("unicode-math","\\upOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\mathrm{\\Omega}, capital omega, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\945', commands :: [(Text, Text)]
commands = [("base","\\alpha"),("omlmathrm","\\mathrm{\\alpha}"),("unicode-math","\\upalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\alphaup (kpfonts mathdesign), = \\upalpha (upgreek), alpha, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\946', commands :: [(Text, Text)]
commands = [("base","\\beta"),("omlmathrm","\\mathrm{\\beta}"),("unicode-math","\\upbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\betaup (kpfonts mathdesign), = \\upbeta (upgreek), beta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\947', commands :: [(Text, Text)]
commands = [("base","\\gamma"),("omlmathrm","\\mathrm{\\gamma}"),("unicode-math","\\upgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\gammaup (kpfonts mathdesign), = \\upgamma (upgreek), gamma, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\948', commands :: [(Text, Text)]
commands = [("base","\\delta"),("omlmathrm","\\mathrm{\\delta}"),("unicode-math","\\updelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\deltaup (kpfonts mathdesign), = \\updelta (upgreek), delta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\949', commands :: [(Text, Text)]
commands = [("base","\\varepsilon"),("omlmathrm","\\mathrm{\\varepsilon}"),("unicode-math","\\upepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varepsilonup (kpfonts mathdesign), = \\upepsilon (upgreek), rounded epsilon, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\950', commands :: [(Text, Text)]
commands = [("base","\\zeta"),("omlmathrm","\\mathrm{\\zeta}"),("unicode-math","\\upzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\zetaup (kpfonts mathdesign), = \\upzeta (upgreek), zeta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\951', commands :: [(Text, Text)]
commands = [("base","\\eta"),("omlmathrm","\\mathrm{\\eta}"),("unicode-math","\\upeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\etaup (kpfonts mathdesign), = \\upeta (upgreek), eta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\952', commands :: [(Text, Text)]
commands = [("base","\\theta"),("omlmathrm","\\mathrm{\\theta}"),("unicode-math","\\uptheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\thetaup (kpfonts mathdesign), straight theta, = \\uptheta (upgreek), theta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\953', commands :: [(Text, Text)]
commands = [("base","\\iota"),("omlmathrm","\\mathrm{\\iota}"),("unicode-math","\\upiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\iotaup (kpfonts mathdesign), = \\upiota (upgreek), iota, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\954', commands :: [(Text, Text)]
commands = [("base","\\kappa"),("omlmathrm","\\mathrm{\\kappa}"),("unicode-math","\\upkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\kappaup (kpfonts mathdesign), = \\upkappa (upgreek), kappa, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\955', commands :: [(Text, Text)]
commands = [("base","\\lambda"),("omlmathrm","\\mathrm{\\lambda}"),("unicode-math","\\uplambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\lambdaup (kpfonts mathdesign), = \\uplambda (upgreek), lambda, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\956', commands :: [(Text, Text)]
commands = [("base","\\mu"),("omlmathrm","\\mathrm{\\mu}"),("unicode-math","\\upmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\muup (kpfonts mathdesign), = \\upmu (upgreek), mu, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\957', commands :: [(Text, Text)]
commands = [("base","\\nu"),("omlmathrm","\\mathrm{\\nu}"),("unicode-math","\\upnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\nuup (kpfonts mathdesign), = \\upnu (upgreek), nu, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\958', commands :: [(Text, Text)]
commands = [("base","\\xi"),("omlmathrm","\\mathrm{\\xi}"),("unicode-math","\\upxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\xiup (kpfonts mathdesign), = \\upxi (upgreek), xi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\959', commands :: [(Text, Text)]
commands = [("unicode-math","\\upomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "small omicron, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\960', commands :: [(Text, Text)]
commands = [("base","\\pi"),("omlmathrm","\\mathrm{\\pi}"),("unicode-math","\\uppi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\piup (kpfonts mathdesign), = \\uppi (upgreek), pi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\961', commands :: [(Text, Text)]
commands = [("base","\\rho"),("omlmathrm","\\mathrm{\\rho}"),("unicode-math","\\uprho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\rhoup (kpfonts mathdesign), = \\uprho (upgreek), rho, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\962', commands :: [(Text, Text)]
commands = [("base","\\varsigma"),("omlmathrm","\\mathrm{\\varsigma}"),("unicode-math","\\upvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varsigmaup (kpfonts mathdesign), = \\upvarsigma (upgreek), terminal sigma, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\963', commands :: [(Text, Text)]
commands = [("base","\\sigma"),("omlmathrm","\\mathrm{\\sigma}"),("unicode-math","\\upsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\sigmaup (kpfonts mathdesign), = \\upsigma (upgreek), sigma, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\964', commands :: [(Text, Text)]
commands = [("base","\\tau"),("omlmathrm","\\mathrm{\\tau}"),("unicode-math","\\uptau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\tauup (kpfonts mathdesign), = \\uptau (upgreek), tau, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\965', commands :: [(Text, Text)]
commands = [("base","\\upsilon"),("omlmathrm","\\mathrm{\\upsilon}"),("unicode-math","\\upupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\upsilonup (kpfonts mathdesign), = \\upupsilon (upgreek), upsilon, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\966', commands :: [(Text, Text)]
commands = [("base","\\varphi"),("omlmathrm","\\mathrm{\\varphi}"),("unicode-math","\\upvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varphiup (kpfonts mathdesign), = \\upvarphi (upgreek), curly or open phi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\967', commands :: [(Text, Text)]
commands = [("base","\\chi"),("omlmathrm","\\mathrm{\\chi}"),("unicode-math","\\upchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\chiup (kpfonts mathdesign), = \\upchi (upgreek), chi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\968', commands :: [(Text, Text)]
commands = [("base","\\psi"),("omlmathrm","\\mathrm{\\psi}"),("unicode-math","\\uppsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\psiup (kpfonts mathdesign), = \\uppsi (upgreek), psi, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\969', commands :: [(Text, Text)]
commands = [("base","\\omega"),("omlmathrm","\\mathrm{\\omega}"),("unicode-math","\\upomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\omegaup (kpfonts mathdesign), = \\upomega (upgreek), omega, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\976', commands :: [(Text, Text)]
commands = [("arevmath","\\varbeta"),("unicode-math","\\upvarbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "rounded beta, greek"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\977', commands :: [(Text, Text)]
commands = [("base","\\vartheta"),("omlmathrm","\\mathrm{\\vartheta}"),("unicode-math","\\upvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varthetaup (kpfonts mathdesign), curly or open theta"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\978', commands :: [(Text, Text)]
commands = [("base","\\mathrm{\\Upsilon}"),("unicode-math","\\upUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "GREEK UPSILON WITH HOOK SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\981', commands :: [(Text, Text)]
commands = [("base","\\phi"),("omlmathrm","\\mathrm{\\phi}"),("unicode-math","\\upphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\phiup (kpfonts mathdesign), GREEK PHI SYMBOL (straight)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\982', commands :: [(Text, Text)]
commands = [("base","\\varpi"),("omlmathrm","\\mathrm{\\varpi}"),("unicode-math","\\upvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varpiup (kpfonts mathdesign), GREEK PI SYMBOL (pomega)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\984', commands :: [(Text, Text)]
commands = [("arevmath","\\Qoppa"),("wrisym","\\Koppa"),("unicode-math","\\upoldKoppa")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "t \\Qoppa (LGR), GREEK LETTER ARCHAIC KOPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\985', commands :: [(Text, Text)]
commands = [("arevmath","\\qoppa"),("wrisym","\\koppa"),("unicode-math","\\upoldkoppa")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "t \\qoppa (LGR), GREEK SMALL LETTER ARCHAIC KOPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\986', commands :: [(Text, Text)]
commands = [("arevmath","\\Stigma"),("wrisym","\\Stigma"),("unicode-math","\\upStigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital stigma"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\987', commands :: [(Text, Text)]
commands = [("arevmath","\\stigma"),("wrisym","\\stigma"),("unicode-math","\\upstigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "GREEK SMALL LETTER STIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\988', commands :: [(Text, Text)]
commands = [("wrisym","\\Digamma"),("amssymb","\\digamma"),("unicode-math","\\upDigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital digamma"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\989', commands :: [(Text, Text)]
commands = [("arevmath","\\digamma"),("wrisym","\\digamma"),("unicode-math","\\updigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "GREEK SMALL LETTER DIGAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\990', commands :: [(Text, Text)]
commands = [("arevmath","\\Koppa"),("unicode-math","\\upKoppa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital koppa"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\991', commands :: [(Text, Text)]
commands = [("arevmath","\\koppa"),("unicode-math","\\upkoppa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "GREEK SMALL LETTER KOPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\992', commands :: [(Text, Text)]
commands = [("arevmath","\\Sampi"),("wrisym","\\Sampi"),("unicode-math","\\upSampi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "capital sampi"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\993', commands :: [(Text, Text)]
commands = [("arevmath","\\sampi"),("wrisym","\\sampi"),("unicode-math","\\upsampi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "GREEK SMALL LETTER SAMPI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\1008', commands :: [(Text, Text)]
commands = [("unicode-math","\\upvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "GREEK KAPPA SYMBOL (round)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\1009', commands :: [(Text, Text)]
commands = [("base","\\varrho"),("omlmathrm","\\mathrm{\\varrho}"),("unicode-math","\\upvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varrhoup (kpfonts mathdesign), GREEK RHO SYMBOL (round)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\1012', commands :: [(Text, Text)]
commands = [("unicode-math","\\upvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "x \\varTheta (amssymb), GREEK CAPITAL THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\1013', commands :: [(Text, Text)]
commands = [("base","\\epsilon"),("omlmathrm","\\mathrm{\\epsilon}"),("unicode-math","\\upvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\epsilonup (kpfonts mathdesign), GREEK LUNATE EPSILON SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\1014', commands :: [(Text, Text)]
commands = [("amssymb","\\backepsilon"),("wrisym","\\backepsilon"),("unicode-math","\\upbackepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "GREEK REVERSED LUNATE EPSILON SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\1064', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "t \\CYRSHHA (T2A), Shcy, CYRILLIC CAPITAL LETTER SHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8192', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "enquad"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8193', commands :: [(Text, Text)]
commands = [("base","\\quad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "emquad"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8194', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ensp (half an em)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8195', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "emsp"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8196', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "THREE-PER-EM SPACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8197', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FOUR-PER-EM SPACE, mid space"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8198', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SIX-PER-EM SPACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8199', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FIGURE SPACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8201', commands :: [(Text, Text)]
commands = [("base","\\,")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "THIN SPACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8202', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HAIR SPACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8203', commands :: [(Text, Text)]
commands = [("base","\\hspace{0pt}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "zwsp"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8208', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HYPHEN (true graphic)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8210', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8211', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ndash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8212', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mdash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8213', commands :: [(Text, Text)]
commands = [("unicode-math","\\horizbar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HORIZONTAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8214', commands :: [(Text, Text)]
commands = [("base","\\|"),("base","\\Vert"),("unicode-math","\\Vert")], category :: TeXSymbolType
category = TeXSymbolType
Fence, comments :: Text
comments = "double vertical bar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8215', commands :: [(Text, Text)]
commands = [("unicode-math","\\twolowline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE LOW LINE (spacing)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8220', commands :: [(Text, Text)]
commands = [("base","``")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = "Opening curly quote"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8221', commands :: [(Text, Text)]
commands = [("base","\"")], category :: TeXSymbolType
category = TeXSymbolType
Pun, comments :: Text
comments = "Closing curly quote"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8224', commands :: [(Text, Text)]
commands = [("base","\\dagger"),("unicode-math","\\dagger")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DAGGER relation"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8225', commands :: [(Text, Text)]
commands = [("base","\\ddagger"),("unicode-math","\\ddagger")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOUBLE DAGGER relation"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8226', commands :: [(Text, Text)]
commands = [("base","\\bullet"),("unicode-math","\\smblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "b: round BULLET, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8229', commands :: [(Text, Text)]
commands = [("unicode-math","\\enleadertwodots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "double baseline dot (en leader)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8230', commands :: [(Text, Text)]
commands = [("base","\\ldots"),("unicode-math","\\unicodeellipsis")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ellipsis (horizontal)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8242', commands :: [(Text, Text)]
commands = [("base","\\prime"),("unicode-math","\\prime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PRIME or minute, not superscripted"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8243', commands :: [(Text, Text)]
commands = [("mathabx","\\second"),("unicode-math","\\dprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE PRIME or second, not superscripted"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8244', commands :: [(Text, Text)]
commands = [("mathabx","\\third"),("unicode-math","\\trprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TRIPLE PRIME (not superscripted)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8245', commands :: [(Text, Text)]
commands = [("amssymb","\\backprime"),("unicode-math","\\backprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "reverse prime, not superscripted"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8246', commands :: [(Text, Text)]
commands = [("unicode-math","\\backdprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "double reverse prime, not superscripted"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8247', commands :: [(Text, Text)]
commands = [("unicode-math","\\backtrprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "triple reverse prime, not superscripted"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8248', commands :: [(Text, Text)]
commands = [("unicode-math","\\caretinsert")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CARET (insertion mark)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8251', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "REFERENCE MARK, Japanese kome jirushi"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8252', commands :: [(Text, Text)]
commands = [("base","!!"),("unicode-math","\\Exclam")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE EXCLAMATION MARK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8256', commands :: [(Text, Text)]
commands = [("oz","\\cat"),("unicode-math","\\tieconcat")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CHARACTER TIE, z notation sequence concatenation"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8259', commands :: [(Text, Text)]
commands = [("unicode-math","\\hyphenbullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "rectangle, filled (HYPHEN BULLET)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8260', commands :: [(Text, Text)]
commands = [("base","/"),("unicode-math","\\fracslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "FRACTION SLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8263', commands :: [(Text, Text)]
commands = [("base","??"),("unicode-math","\\Question")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE QUESTION MARK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8270', commands :: [(Text, Text)]
commands = [("base","\\ast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "lowast, LOW ASTERISK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8271', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "bsemi, REVERSED SEMICOLON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8272', commands :: [(Text, Text)]
commands = [("unicode-math","\\closure")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CLOSE UP (editing mark)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8273', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "Ast"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8274', commands :: [(Text, Text)]
commands = [("base","./.")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "COMMERCIAL MINUS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8279', commands :: [(Text, Text)]
commands = [("mathabx","\\fourth"),("unicode-math","\\qprime")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "QUADRUPLE PRIME, not superscripted"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8287', commands :: [(Text, Text)]
commands = [("base","\\:"),("amsmath","\\medspace")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEDIUM MATHEMATICAL SPACE, four-eighteenths of an em"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8289', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FUNCTION APPLICATION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8290', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INVISIBLE TIMES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8291', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INVISIBLE SEPARATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8292', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INVISIBLE PLUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8314', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUPERSCRIPT PLUS SIGN subscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8315', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUPERSCRIPT MINUS subscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8316', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUPERSCRIPT EQUALS SIGN subscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8317', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "SUPERSCRIPT LEFT PARENTHESIS subscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8318', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "SUPERSCRIPT RIGHT PARENTHESIS subscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8330', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUBSCRIPT PLUS SIGN superscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8331', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUBSCRIPT MINUS superscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8332', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUBSCRIPT EQUALS SIGN superscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8333', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "SUBSCRIPT LEFT PARENTHESIS superscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8334', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "SUBSCRIPT RIGHT PARENTHESIS superscript operators"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8364', commands :: [(Text, Text)]
commands = [("unicode-math","\\euro")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EURO SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8400', commands :: [(Text, Text)]
commands = [("wrisym","\\lvec"),("unicode-math","\\leftharpoonaccent")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LEFT HARPOON ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8401', commands :: [(Text, Text)]
commands = [("wrisym","\\vec"),("unicode-math","\\rightharpoonaccent")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING RIGHT HARPOON ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8402', commands :: [(Text, Text)]
commands = [("unicode-math","\\vertoverlay")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LONG VERTICAL LINE OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8403', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING SHORT VERTICAL LINE OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8404', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ANTICLOCKWISE ARROW ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8406', commands :: [(Text, Text)]
commands = [("wrisym","\\LVec"),("base","\\overleftarrow"),("unicode-math","\\overleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LEFT ARROW ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8407', commands :: [(Text, Text)]
commands = [("base","\\vec"),("wrisym","\\Vec"),("unicode-math","\\vec")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "# \\overrightarrow, COMBINING RIGHT ARROW ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8408', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING RING OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8409', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING CLOCKWISE RING OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8410', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ANTICLOCKWISE RING OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8411', commands :: [(Text, Text)]
commands = [("amsmath","\\dddot"),("wrisym","\\DDDot"),("unicode-math","\\dddot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING THREE DOTS ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8412', commands :: [(Text, Text)]
commands = [("amsmath","\\ddddot"),("unicode-math","\\ddddot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING FOUR DOTS ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8413', commands :: [(Text, Text)]
commands = [("unicode-math","\\enclosecircle")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ENCLOSING CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8414', commands :: [(Text, Text)]
commands = [("unicode-math","\\enclosesquare")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ENCLOSING SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8415', commands :: [(Text, Text)]
commands = [("unicode-math","\\enclosediamond")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ENCLOSING DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8417', commands :: [(Text, Text)]
commands = [("amsmath","\\overleftrightarrow"),("unicode-math","\\overleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LEFT RIGHT ARROW ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8420', commands :: [(Text, Text)]
commands = [("unicode-math","\\enclosetriangle")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ENCLOSING UPWARD POINTING TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8421', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING REVERSE SOLIDUS OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8422', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING DOUBLE VERTICAL STROKE OVERLAY, z notation finite function diacritic"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8423', commands :: [(Text, Text)]
commands = [("unicode-math","\\annuity")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ANNUITY SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8424', commands :: [(Text, Text)]
commands = [("unicode-math","\\threeunderdot")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING TRIPLE UNDERDOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8425', commands :: [(Text, Text)]
commands = [("unicode-math","\\widebridgeabove")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING WIDE BRIDGE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8426', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LEFTWARDS ARROW OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8427', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LONG DOUBLE SOLIDUS OVERLAY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8428', commands :: [(Text, Text)]
commands = [("unicode-math","\\underrightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING RIGHTWARDS HARPOON WITH BARB DOWNWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8429', commands :: [(Text, Text)]
commands = [("unicode-math","\\underleftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LEFTWARDS HARPOON WITH BARB DOWNWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8430', commands :: [(Text, Text)]
commands = [("amsmath","\\underleftarrow"),("unicode-math","\\underleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING LEFT ARROW BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8431', commands :: [(Text, Text)]
commands = [("amsmath","\\underrightarrow"),("unicode-math","\\underrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING RIGHT ARROW BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8432', commands :: [(Text, Text)]
commands = [("unicode-math","\\asteraccent")], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "COMBINING ASTERISK ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8450', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{C}"),("dsfont","\\mathds{C}"),("unicode-math","\\BbbC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "open face C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8455', commands :: [(Text, Text)]
commands = [("wrisym","\\Euler"),("unicode-math","\\Eulerconst")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EULER CONSTANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8458', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{g}"),("unicode-math","\\mscrg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/scr g, script small letter g"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8459', commands :: [(Text, Text)]
commands = [("base","\\mathcal{H}"),("unicode-math","\\mscrH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "hamiltonian (script capital H)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8460', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{H}"),("unicode-math","\\mfrakH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/frak H, black-letter capital H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8461', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{H}"),("dsfont","\\mathds{H}"),("unicode-math","\\BbbH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "open face capital H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8462', commands :: [(Text, Text)]
commands = [("base","h"),("unicode-math","\\Planckconst")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "Planck constant"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8463', commands :: [(Text, Text)]
commands = [("amssymb","\\hslash"),("fourier","\\hslash"),("arevmath","\\hslash"),("wrisym","\\HBar"),("unicode-math","\\hslash")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "#\\hbar, Planck's h over 2pi"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8464', commands :: [(Text, Text)]
commands = [("base","\\mathcal{I}"),("unicode-math","\\mscrI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/scr I, script capital I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8465', commands :: [(Text, Text)]
commands = [("base","\\Im"),("eufrak","\\mathfrak{I}"),("unicode-math","\\Im")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "imaginary part"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8466', commands :: [(Text, Text)]
commands = [("base","\\mathcal{L}"),("unicode-math","\\mscrL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "lagrangian (script capital L)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8467', commands :: [(Text, Text)]
commands = [("base","\\ell"),("unicode-math","\\ell")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "cursive small l"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8469', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{N}"),("dsfont","\\mathds{N}"),("unicode-math","\\BbbN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "open face N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8472', commands :: [(Text, Text)]
commands = [("amssymb","\\wp"),("unicode-math","\\wp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "weierstrass p"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8473', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{P}"),("dsfont","\\mathds{P}"),("unicode-math","\\BbbP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "open face P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8474', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{Q}"),("dsfont","\\mathds{Q}"),("unicode-math","\\BbbQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "open face Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8475', commands :: [(Text, Text)]
commands = [("base","\\mathcal{R}"),("unicode-math","\\mscrR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/scr R, script capital R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8476', commands :: [(Text, Text)]
commands = [("base","\\Re"),("eufrak","\\mathfrak{R}"),("unicode-math","\\Re")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "real part"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8477', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{R}"),("dsfont","\\mathds{R}"),("unicode-math","\\BbbR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "open face R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8484', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{Z}"),("dsfont","\\mathds{Z}"),("unicode-math","\\BbbZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "open face Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8486', commands :: [(Text, Text)]
commands = [("mathcomp","\\tcohm"),("base","\\mathrm{\\Omega}")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "ohm (deprecated in math, use greek letter)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8487', commands :: [(Text, Text)]
commands = [("amsfonts","\\mho"),("arevmath","\\mho"),("wrisym","\\Mho"),("unicode-math","\\mho")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "t \\agemO (wasysym), conductance"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8488', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{Z}"),("unicode-math","\\mfrakZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/frak Z, black-letter capital Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8489', commands :: [(Text, Text)]
commands = [("unicode-math","\\turnediota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "turned iota"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8491', commands :: [(Text, Text)]
commands = [("wrisym","\\Angstroem"),("base","\\mathring{\\mathrm{A}}"),("unicode-math","\\Angstrom")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "\197ngstr\246m capital A with ring"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8492', commands :: [(Text, Text)]
commands = [("base","\\mathcal{B}"),("unicode-math","\\mscrB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "bernoulli function (script capital B)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8493', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{C}"),("unicode-math","\\mfrakC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "black-letter capital C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8495', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{e}"),("unicode-math","\\mscre")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/scr e, script small letter e"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8496', commands :: [(Text, Text)]
commands = [("base","\\mathcal{E}"),("unicode-math","\\mscrE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/scr E, script capital E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8497', commands :: [(Text, Text)]
commands = [("base","\\mathcal{F}"),("unicode-math","\\mscrF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "/scr F, script capital F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8498', commands :: [(Text, Text)]
commands = [("amssymb","\\Finv"),("unicode-math","\\Finv")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TURNED CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8499', commands :: [(Text, Text)]
commands = [("base","\\mathcal{M}"),("unicode-math","\\mscrM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "physics m-matrix (SCRIPT CAPITAL M)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8500', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{o}"),("unicode-math","\\mscro")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "order of (SCRIPT SMALL O)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8501', commands :: [(Text, Text)]
commands = [("base","\\aleph"),("unicode-math","\\aleph")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "aleph, hebrew"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8502', commands :: [(Text, Text)]
commands = [("amssymb","\\beth"),("wrisym","\\beth"),("unicode-math","\\beth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "beth, hebrew"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8503', commands :: [(Text, Text)]
commands = [("amssymb","\\gimel"),("wrisym","\\gimel"),("unicode-math","\\gimel")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "gimel, hebrew"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8504', commands :: [(Text, Text)]
commands = [("amssymb","\\daleth"),("wrisym","\\daleth"),("unicode-math","\\daleth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "daleth, hebrew"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8508', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{\\pi}"),("unicode-math","\\Bbbpi")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "\\DoublePi (wrisym), DOUBLE-STRUCK SMALL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8509', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{\\gamma}"),("unicode-math","\\Bbbgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "\\EulerGamma (wrisym), DOUBLE-STRUCK SMALL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8510', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{\\Gamma}"),("unicode-math","\\BbbGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "DOUBLE-STRUCK CAPITAL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8511', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{\\Pi}"),("unicode-math","\\BbbPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "DOUBLE-STRUCK CAPITAL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8512', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{\\Sigma}"),("unicode-math","\\Bbbsum")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "DOUBLE-STRUCK N-ARY SUMMATION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8513', commands :: [(Text, Text)]
commands = [("amssymb","\\Game"),("unicode-math","\\Game")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TURNED SANS-SERIF CAPITAL G (amssymb has mirrored G)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8514', commands :: [(Text, Text)]
commands = [("unicode-math","\\sansLturned")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TURNED SANS-SERIF CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8515', commands :: [(Text, Text)]
commands = [("unicode-math","\\sansLmirrored")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "REVERSED SANS-SERIF CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8516', commands :: [(Text, Text)]
commands = [("stmaryrd","\\Yup"),("unicode-math","\\Yup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TURNED SANS-SERIF CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8517', commands :: [(Text, Text)]
commands = [("wrisym","\\CapitalDifferentialD"),("wrisym","\\DD"),("unicode-math","\\mitBbbD")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE-STRUCK ITALIC CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8518', commands :: [(Text, Text)]
commands = [("wrisym","\\DifferentialD"),("wrisym","\\dd"),("unicode-math","\\mitBbbd")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE-STRUCK ITALIC SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8519', commands :: [(Text, Text)]
commands = [("wrisym","\\ExponetialE"),("wrisym","\\ee"),("unicode-math","\\mitBbbe")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE-STRUCK ITALIC SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8520', commands :: [(Text, Text)]
commands = [("wrisym","\\ComplexI"),("wrisym","\\ii"),("unicode-math","\\mitBbbi")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE-STRUCK ITALIC SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8521', commands :: [(Text, Text)]
commands = [("wrisym","\\ComplexJ"),("wrisym","\\jj"),("unicode-math","\\mitBbbj")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOUBLE-STRUCK ITALIC SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8522', commands :: [(Text, Text)]
commands = [("unicode-math","\\PropertyLine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PROPERTY LINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8523', commands :: [(Text, Text)]
commands = [("txfonts","\\invamp"),("stmaryrd","\\bindnasrepma"),("unicode-math","\\upand")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TURNED AMPERSAND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8592', commands :: [(Text, Text)]
commands = [("base","\\leftarrow"),("base","\\gets"),("unicode-math","\\leftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "a: leftward arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8593', commands :: [(Text, Text)]
commands = [("base","\\uparrow"),("unicode-math","\\uparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "upward arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8594', commands :: [(Text, Text)]
commands = [("base","\\rightarrow"),("base","\\to"),("unicode-math","\\rightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\tfun (oz), = \\fun (oz), rightward arrow, z notation total function"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8595', commands :: [(Text, Text)]
commands = [("base","\\downarrow"),("unicode-math","\\downarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "downward arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8596', commands :: [(Text, Text)]
commands = [("base","\\leftrightarrow"),("oz","\\rel"),("unicode-math","\\leftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT RIGHT ARROW, z notation relation"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8597', commands :: [(Text, Text)]
commands = [("base","\\updownarrow"),("unicode-math","\\updownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "up and down arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8598', commands :: [(Text, Text)]
commands = [("amssymb","\\nwarrow"),("unicode-math","\\nwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "nw pointing arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8599', commands :: [(Text, Text)]
commands = [("base","\\nearrow"),("unicode-math","\\nearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ne pointing arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8600', commands :: [(Text, Text)]
commands = [("base","\\searrow"),("unicode-math","\\searrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "se pointing arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8601', commands :: [(Text, Text)]
commands = [("base","\\swarrow"),("unicode-math","\\swarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "sw pointing arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8602', commands :: [(Text, Text)]
commands = [("amssymb","\\nleftarrow"),("unicode-math","\\nleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not left arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8603', commands :: [(Text, Text)]
commands = [("amssymb","\\nrightarrow"),("unicode-math","\\nrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not right arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8604', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftwavearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left arrow-wavy"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8605', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightwavearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right arrow-wavy"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8606', commands :: [(Text, Text)]
commands = [("amssymb","\\twoheadleftarrow"),("unicode-math","\\twoheadleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left two-headed arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8607', commands :: [(Text, Text)]
commands = [("unicode-math","\\twoheaduparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "up two-headed arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8608', commands :: [(Text, Text)]
commands = [("amssymb","\\twoheadrightarrow"),("oz","\\tsur"),("unicode-math","\\twoheadrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\surj (oz), right two-headed arrow, z notation total surjection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8609', commands :: [(Text, Text)]
commands = [("unicode-math","\\twoheaddownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "down two-headed arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8610', commands :: [(Text, Text)]
commands = [("amssymb","\\leftarrowtail"),("unicode-math","\\leftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left arrow-tailed"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8611', commands :: [(Text, Text)]
commands = [("amssymb","\\rightarrowtail"),("oz","\\tinj"),("unicode-math","\\rightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\inj (oz), right arrow-tailed, z notation total injection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8612', commands :: [(Text, Text)]
commands = [("stmaryrd","\\mapsfrom"),("kpfonts","\\mappedfrom"),("unicode-math","\\mapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "maps to, leftward"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8613', commands :: [(Text, Text)]
commands = [("wrisym","\\MapsUp"),("unicode-math","\\mapsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "maps to, upward"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8614', commands :: [(Text, Text)]
commands = [("base","\\mapsto"),("unicode-math","\\mapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "maps to, rightward, z notation maplet"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8615', commands :: [(Text, Text)]
commands = [("wrisym","\\MapsDown"),("unicode-math","\\mapsdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "maps to, downward"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8616', commands :: [(Text, Text)]
commands = [("unicode-math","\\updownarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UP DOWN ARROW WITH BASE (perpendicular)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8617', commands :: [(Text, Text)]
commands = [("base","\\hookleftarrow"),("unicode-math","\\hookleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left arrow-hooked"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8618', commands :: [(Text, Text)]
commands = [("base","\\hookrightarrow"),("unicode-math","\\hookrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right arrow-hooked"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8619', commands :: [(Text, Text)]
commands = [("amssymb","\\looparrowleft"),("unicode-math","\\looparrowleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left arrow-looped"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8620', commands :: [(Text, Text)]
commands = [("amssymb","\\looparrowright"),("unicode-math","\\looparrowright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right arrow-looped"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8621', commands :: [(Text, Text)]
commands = [("amssymb","\\leftrightsquigarrow"),("unicode-math","\\leftrightsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left and right arr-wavy"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8622', commands :: [(Text, Text)]
commands = [("amssymb","\\nleftrightarrow"),("unicode-math","\\nleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not left and right arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8623', commands :: [(Text, Text)]
commands = [("stmaryrd","\\lightning"),("unicode-math","\\downzigzagarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "t \\Lightning (marvosym), DOWNWARDS ZIGZAG ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8624', commands :: [(Text, Text)]
commands = [("amssymb","\\Lsh"),("unicode-math","\\Lsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "a: UPWARDS ARROW WITH TIP LEFTWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8625', commands :: [(Text, Text)]
commands = [("amssymb","\\Rsh"),("unicode-math","\\Rsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "a: UPWARDS ARROW WITH TIP RIGHTWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8626', commands :: [(Text, Text)]
commands = [("mathabx","\\dlsh"),("unicode-math","\\Ldsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left down angled arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8627', commands :: [(Text, Text)]
commands = [("mathabx","\\drsh"),("unicode-math","\\Rdsh")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right down angled arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8628', commands :: [(Text, Text)]
commands = [("unicode-math","\\linefeed")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHTWARDS ARROW WITH CORNER DOWNWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8629', commands :: [(Text, Text)]
commands = [("unicode-math","\\carriagereturn")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "downwards arrow with corner leftward = carriage return"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8630', commands :: [(Text, Text)]
commands = [("amssymb","\\curvearrowleft"),("fourier","\\curvearrowleft"),("unicode-math","\\curvearrowleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left curved arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8631', commands :: [(Text, Text)]
commands = [("amssymb","\\curvearrowright"),("fourier","\\curvearrowright"),("unicode-math","\\curvearrowright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right curved arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8632', commands :: [(Text, Text)]
commands = [("unicode-math","\\barovernorthwestarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH WEST ARROW TO LONG BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8633', commands :: [(Text, Text)]
commands = [("unicode-math","\\barleftarrowrightarrowba")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFTWARDS ARROW TO BAR OVER RIGHTWARDS ARROW TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8634', commands :: [(Text, Text)]
commands = [("amssymb","\\circlearrowleft"),("wasysym","\\leftturn"),("unicode-math","\\acwopencirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ANTICLOCKWISE OPEN CIRCLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8635', commands :: [(Text, Text)]
commands = [("amssymb","\\circlearrowright"),("wasysym","\\rightturn"),("unicode-math","\\cwopencirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CLOCKWISE OPEN CIRCLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8636', commands :: [(Text, Text)]
commands = [("base","\\leftharpoonup"),("unicode-math","\\leftharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left harpoon-up"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8637', commands :: [(Text, Text)]
commands = [("base","\\leftharpoondown"),("unicode-math","\\leftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left harpoon-down"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8638', commands :: [(Text, Text)]
commands = [("amssymb","\\upharpoonright"),("amssymb","\\restriction"),("unicode-math","\\upharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\upharpoonrightup (wrisym), a: up harpoon-right"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8639', commands :: [(Text, Text)]
commands = [("amssymb","\\upharpoonleft"),("wrisym","\\upharpoonleftup"),("unicode-math","\\upharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "up harpoon-left"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8640', commands :: [(Text, Text)]
commands = [("base","\\rightharpoonup"),("unicode-math","\\rightharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right harpoon-up"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8641', commands :: [(Text, Text)]
commands = [("base","\\rightharpoondown"),("unicode-math","\\rightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right harpoon-down"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8642', commands :: [(Text, Text)]
commands = [("amssymb","\\downharpoonright"),("wrisym","\\upharpoonrightdown"),("unicode-math","\\downharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "down harpoon-right"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8643', commands :: [(Text, Text)]
commands = [("amssymb","\\downharpoonleft"),("wrisym","\\upharpoonleftdown"),("unicode-math","\\downharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "down harpoon-left"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8644', commands :: [(Text, Text)]
commands = [("amssymb","\\rightleftarrows"),("wrisym","\\rightleftarrow"),("unicode-math","\\rightleftarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right arrow over left arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8645', commands :: [(Text, Text)]
commands = [("mathabx","\\updownarrows"),("wrisym","\\uparrowdownarrow"),("unicode-math","\\updownarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "up arrow, down arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8646', commands :: [(Text, Text)]
commands = [("amssymb","\\leftrightarrows"),("wrisym","\\leftrightarrow"),("unicode-math","\\leftrightarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left arrow over right arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8647', commands :: [(Text, Text)]
commands = [("amssymb","\\leftleftarrows"),("fourier","\\leftleftarrows"),("unicode-math","\\leftleftarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "two left arrows"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8648', commands :: [(Text, Text)]
commands = [("amssymb","\\upuparrows"),("unicode-math","\\upuparrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "two up arrows"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8649', commands :: [(Text, Text)]
commands = [("amssymb","\\rightrightarrows"),("fourier","\\rightrightarrows"),("unicode-math","\\rightrightarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "two right arrows"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8650', commands :: [(Text, Text)]
commands = [("amssymb","\\downdownarrows"),("unicode-math","\\downdownarrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "two down arrows"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8651', commands :: [(Text, Text)]
commands = [("amssymb","\\leftrightharpoons"),("wrisym","\\revequilibrium"),("unicode-math","\\leftrightharpoons")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left harpoon over right"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8652', commands :: [(Text, Text)]
commands = [("base","\\rightleftharpoons"),("wrisym","\\equilibrium"),("unicode-math","\\rightleftharpoons")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right harpoon over left"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8653', commands :: [(Text, Text)]
commands = [("amssymb","\\nLeftarrow"),("unicode-math","\\nLeftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not implied by"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8654', commands :: [(Text, Text)]
commands = [("amssymb","\\nLeftrightarrow"),("unicode-math","\\nLeftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not left and right double arrows"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8655', commands :: [(Text, Text)]
commands = [("amssymb","\\nRightarrow"),("unicode-math","\\nRightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not implies"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8656', commands :: [(Text, Text)]
commands = [("base","\\Leftarrow"),("unicode-math","\\Leftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8657', commands :: [(Text, Text)]
commands = [("base","\\Uparrow"),("unicode-math","\\Uparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "up double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8658', commands :: [(Text, Text)]
commands = [("base","\\Rightarrow"),("unicode-math","\\Rightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8659', commands :: [(Text, Text)]
commands = [("base","\\Downarrow"),("unicode-math","\\Downarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "down double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8660', commands :: [(Text, Text)]
commands = [("base","\\Leftrightarrow"),("unicode-math","\\Leftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left and right double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8661', commands :: [(Text, Text)]
commands = [("base","\\Updownarrow"),("unicode-math","\\Updownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "up and down double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8662', commands :: [(Text, Text)]
commands = [("txfonts","\\Nwarrow"),("unicode-math","\\Nwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "nw pointing double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8663', commands :: [(Text, Text)]
commands = [("txfonts","\\Nearrow"),("unicode-math","\\Nearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ne pointing double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8664', commands :: [(Text, Text)]
commands = [("txfonts","\\Searrow"),("unicode-math","\\Searrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "se pointing double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8665', commands :: [(Text, Text)]
commands = [("txfonts","\\Swarrow"),("unicode-math","\\Swarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "sw pointing double arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8666', commands :: [(Text, Text)]
commands = [("amssymb","\\Lleftarrow"),("unicode-math","\\Lleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left triple arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8667', commands :: [(Text, Text)]
commands = [("amssymb","\\Rrightarrow"),("unicode-math","\\Rrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right triple arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8668', commands :: [(Text, Text)]
commands = [("mathabx","\\leftsquigarrow"),("txfonts","\\leftsquigarrow"),("unicode-math","\\leftsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS SQUIGGLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8669', commands :: [(Text, Text)]
commands = [("amssymb","\\rightsquigarrow"),("unicode-math","\\rightsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS SQUIGGLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8670', commands :: [(Text, Text)]
commands = [("unicode-math","\\nHuparrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS ARROW WITH DOUBLE STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8671', commands :: [(Text, Text)]
commands = [("unicode-math","\\nHdownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWNWARDS ARROW WITH DOUBLE STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8672', commands :: [(Text, Text)]
commands = [("amsfonts","\\dashleftarrow"),("unicode-math","\\leftdasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFTWARDS DASHED ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8673', commands :: [(Text, Text)]
commands = [("unicode-math","\\updasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS DASHED ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8674', commands :: [(Text, Text)]
commands = [("amsfonts","\\dashrightarrow"),("amsfonts","\\dasharrow"),("unicode-math","\\rightdasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHTWARDS DASHED ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8675', commands :: [(Text, Text)]
commands = [("unicode-math","\\downdasharrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWNWARDS DASHED ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8676', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftArrowBar"),("unicode-math","\\barleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8677', commands :: [(Text, Text)]
commands = [("wrisym","\\RightArrowBar"),("unicode-math","\\rightarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8678', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFTWARDS WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8679', commands :: [(Text, Text)]
commands = [("unicode-math","\\upwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8680', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHTWARDS WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8681', commands :: [(Text, Text)]
commands = [("unicode-math","\\downwhitearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWNWARDS WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8682', commands :: [(Text, Text)]
commands = [("unicode-math","\\whitearrowupfrombar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS WHITE ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8683', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS WHITE ARROW ON PEDESTAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8684', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS WHITE ARROW ON PEDESTAL WITH HORIZONTAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8685', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS WHITE ARROW ON PEDESTAL WITH VERTICAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8686', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS WHITE DOUBLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8687', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS WHITE DOUBLE ARROW ON PEDESTAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8688', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHTWARDS WHITE ARROW FROM WALL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8689', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH WEST ARROW TO CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8690', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SOUTH EAST ARROW TO CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8691', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UP DOWN WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8692', commands :: [(Text, Text)]
commands = [("unicode-math","\\circleonrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHT ARROW WITH SMALL CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8693', commands :: [(Text, Text)]
commands = [("mathabx","\\downuparrows"),("wrisym","\\downarrowuparrow"),("unicode-math","\\downuparrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS ARROW LEFTWARDS OF UPWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8694', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightthreearrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "THREE RIGHTWARDS ARROWS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8695', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW WITH VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8696', commands :: [(Text, Text)]
commands = [("oz","\\pfun"),("unicode-math","\\nvrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW WITH VERTICAL STROKE, z notation partial function"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8697', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT RIGHT ARROW WITH VERTICAL STROKE, z notation partial relation"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8698', commands :: [(Text, Text)]
commands = [("unicode-math","\\nVleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW WITH DOUBLE VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8699', commands :: [(Text, Text)]
commands = [("oz","\\ffun"),("unicode-math","\\nVrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW WITH DOUBLE VERTICAL STROKE, z notation finite function"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8700', commands :: [(Text, Text)]
commands = [("unicode-math","\\nVleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT RIGHT ARROW WITH DOUBLE VERTICAL STROKE, z notation finite relation"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8701', commands :: [(Text, Text)]
commands = [("stmaryrd","\\leftarrowtriangle"),("unicode-math","\\leftarrowtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS OPEN-HEADED ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8702', commands :: [(Text, Text)]
commands = [("stmaryrd","\\rightarrowtriangle"),("unicode-math","\\rightarrowtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS OPEN-HEADED ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8703', commands :: [(Text, Text)]
commands = [("stmaryrd","\\leftrightarrowtriangle"),("unicode-math","\\leftrightarrowtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT RIGHT OPEN-HEADED ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8704', commands :: [(Text, Text)]
commands = [("base","\\forall"),("unicode-math","\\forall")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FOR ALL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8705', commands :: [(Text, Text)]
commands = [("amssymb","\\complement"),("fourier","\\complement"),("unicode-math","\\complement")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "COMPLEMENT sign"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8706', commands :: [(Text, Text)]
commands = [("base","\\partial"),("kpfonts","\\partialup"),("unicode-math","\\partial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PARTIAL DIFFERENTIAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8707', commands :: [(Text, Text)]
commands = [("base","\\exists"),("oz","\\exi"),("unicode-math","\\exists")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "at least one exists"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8708', commands :: [(Text, Text)]
commands = [("amssymb","\\nexists"),("fourier","\\nexists"),("oz","\\nexi"),("unicode-math","\\nexists")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "negated exists"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8709', commands :: [(Text, Text)]
commands = [("amssymb","\\varnothing"),("unicode-math","\\varnothing")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "circle, slash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8710', commands :: [(Text, Text)]
commands = [("base","\\mathrm{\\Delta}"),("unicode-math","\\increment")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "laplacian (Delta; nabla square)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8711', commands :: [(Text, Text)]
commands = [("base","\\nabla"),("unicode-math","\\nabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NABLA, del, hamilton operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8712', commands :: [(Text, Text)]
commands = [("base","\\in"),("unicode-math","\\in")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "set membership, variant"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8713', commands :: [(Text, Text)]
commands = [("base","\\notin"),("wrisym","\\nin"),("unicode-math","\\notin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "negated set membership"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8714', commands :: [(Text, Text)]
commands = [("base","\\in"),("unicode-math","\\smallin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "set membership (small set membership)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8715', commands :: [(Text, Text)]
commands = [("base","\\ni"),("base","\\owns"),("unicode-math","\\ni")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "contains, variant"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8716', commands :: [(Text, Text)]
commands = [("wrisym","\\nni"),("txfonts","\\notni"),("unicode-math","\\nni")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\notowner (mathabx), = \\notowns (fourier), negated contains, variant"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8717', commands :: [(Text, Text)]
commands = [("base","\\ni"), ("unicode-math","\\smallni")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "r: contains (SMALL CONTAINS AS MEMBER)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8718', commands :: [(Text, Text)]
commands = [("amssymb","\\blacksquare"),("unicode-math","\\QED")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "END OF PROOF"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8719', commands :: [(Text, Text)]
commands = [("base","\\prod"),("unicode-math","\\prod")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "product operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8720', commands :: [(Text, Text)]
commands = [("base","\\coprod"),("unicode-math","\\coprod")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "coproduct operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8721', commands :: [(Text, Text)]
commands = [("base","\\sum"),("unicode-math","\\sum")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "summation operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8722', commands :: [(Text, Text)]
commands = [("base","-"),("unicode-math","\\minus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINUS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8723', commands :: [(Text, Text)]
commands = [("base","\\mp"),("unicode-math","\\mp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINUS-OR-PLUS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8724', commands :: [(Text, Text)]
commands = [("amssymb","\\dotplus"),("unicode-math","\\dotplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "plus sign, dot above"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8725', commands :: [(Text, Text)]
commands = [("base","\\slash"),("unicode-math","\\divslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DIVISION SLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8726', commands :: [(Text, Text)]
commands = [("amssymb","\\smallsetminus"),("fourier","\\smallsetminus"),("unicode-math","\\smallsetminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "small SET MINUS (cf. reverse solidus)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8727', commands :: [(Text, Text)]
commands = [("base","\\ast"),("unicode-math","\\ast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "ASTERISK OPERATOR (Hodge star operator)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8728', commands :: [(Text, Text)]
commands = [("base","\\circ"),("unicode-math","\\vysmwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "composite function (small circle)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8729', commands :: [(Text, Text)]
commands = [("base","\\bullet"),("unicode-math","\\vysmblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "BULLET OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8730', commands :: [(Text, Text)]
commands = [("base","\\sqrt"),("unicode-math","\\sqrt")], category :: TeXSymbolType
category = TeXSymbolType
Rad, comments :: Text
comments = "radical"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8731', commands :: [(Text, Text)]
commands = [("base","\\sqrt[3]"),("unicode-math","\\cuberoot")], category :: TeXSymbolType
category = TeXSymbolType
Rad, comments :: Text
comments = "CUBE ROOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8732', commands :: [(Text, Text)]
commands = [("base","\\sqrt[4]"),("unicode-math","\\fourthroot")], category :: TeXSymbolType
category = TeXSymbolType
Rad, comments :: Text
comments = "FOURTH ROOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8733', commands :: [(Text, Text)]
commands = [("base","\\propto"),("amssymb","\\varpropto"),("unicode-math","\\propto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "is PROPORTIONAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8734', commands :: [(Text, Text)]
commands = [("base","\\infty"),("unicode-math","\\infty")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INFINITY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8735', commands :: [(Text, Text)]
commands = [("wrisym","\\rightangle"),("unicode-math","\\rightangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "right (90 degree) angle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8736', commands :: [(Text, Text)]
commands = [("base","\\angle"),("unicode-math","\\angle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8737', commands :: [(Text, Text)]
commands = [("amssymb","\\measuredangle"),("wrisym","\\measuredangle"),("unicode-math","\\measuredangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8738', commands :: [(Text, Text)]
commands = [("amssymb","\\sphericalangle"),("wrisym","\\sphericalangle"),("unicode-math","\\sphericalangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SPHERICAL ANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8739', commands :: [(Text, Text)]
commands = [("base","\\mid"),("unicode-math","\\mid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "r: DIVIDES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8740', commands :: [(Text, Text)]
commands = [("amssymb","\\nmid"),("unicode-math","\\nmid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "negated mid, DOES NOT DIVIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8741', commands :: [(Text, Text)]
commands = [("base","\\parallel"),("unicode-math","\\parallel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "parallel"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8742', commands :: [(Text, Text)]
commands = [("amssymb","\\nparallel"),("fourier","\\nparallel"),("unicode-math","\\nparallel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not parallel"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8743', commands :: [(Text, Text)]
commands = [("amssymb","\\wedge"),("base","\\land"),("unicode-math","\\wedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "b: LOGICAL AND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8744', commands :: [(Text, Text)]
commands = [("base","\\vee"),("base","\\lor"),("unicode-math","\\vee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "b: LOGICAL OR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8745', commands :: [(Text, Text)]
commands = [("base","\\cap"),("unicode-math","\\cap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8746', commands :: [(Text, Text)]
commands = [("base","\\cup"),("unicode-math","\\cup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "UNION or logical sum"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8747', commands :: [(Text, Text)]
commands = [("base","\\int"),("unicode-math","\\int")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8748', commands :: [(Text, Text)]
commands = [("amsmath","\\iint"),("fourier","\\iint"),("esint","\\iint"),("wasysym","\\iint"),("unicode-math","\\iint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "DOUBLE INTEGRAL operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8749', commands :: [(Text, Text)]
commands = [("amsmath","\\iiint"),("fourier","\\iiint"),("esint","\\iiint"),("wasysym","\\iiint"),("unicode-math","\\iiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "TRIPLE INTEGRAL operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8750', commands :: [(Text, Text)]
commands = [("base","\\oint"),("unicode-math","\\oint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "CONTOUR INTEGRAL operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8751', commands :: [(Text, Text)]
commands = [("esint","\\oiint"),("wasysym","\\oiint"),("fourier","\\oiint"),("wrisym","\\dbloint"),("unicode-math","\\oiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "double contour integral operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8752', commands :: [(Text, Text)]
commands = [("txfonts","\\oiiint"),("fourier","\\oiiint"),("unicode-math","\\oiiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "triple contour integral operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8753', commands :: [(Text, Text)]
commands = [("unicode-math","\\intclockwise")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "CLOCKWISE INTEGRAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8754', commands :: [(Text, Text)]
commands = [("esint","\\varointclockwise"),("wrisym","\\clockoint"),("unicode-math","\\varointclockwise")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "contour integral, clockwise"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8755', commands :: [(Text, Text)]
commands = [("esint","\\ointctrclockwise"),("wrisym","\\cntclockoint"),("unicode-math","\\ointctrclockwise")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "contour integral, anticlockwise"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8756', commands :: [(Text, Text)]
commands = [("amssymb","\\therefore"),("wrisym","\\therefore"),("wasysym","\\wasytherefore"),("unicode-math","\\therefore")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "THEREFORE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8757', commands :: [(Text, Text)]
commands = [("amssymb","\\because"),("wrisym","\\because"),("unicode-math","\\because")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BECAUSE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8758', commands :: [(Text, Text)]
commands = [("base",":"),("unicode-math","\\mathratio")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "x \\colon, RATIO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8759', commands :: [(Text, Text)]
commands = [("wrisym","\\Proportion"),("base","::"),("unicode-math","\\Colon")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "two colons"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8760', commands :: [(Text, Text)]
commands = [("unicode-math","\\dotminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "minus sign, dot above"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8761', commands :: [(Text, Text)]
commands = [("txfonts","\\eqcolon"),("base","-:"),("unicode-math","\\dashcolon")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EXCESS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8762', commands :: [(Text, Text)]
commands = [("unicode-math","\\dotsminusdots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "minus with four dots, GEOMETRIC PROPORTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8763', commands :: [(Text, Text)]
commands = [("unicode-math","\\kernelcontraction")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "HOMOTHETIC"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8764', commands :: [(Text, Text)]
commands = [("base","\\sim"),("unicode-math","\\sim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "similar to, TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8765', commands :: [(Text, Text)]
commands = [("amssymb","\\backsim"),("unicode-math","\\backsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "reverse similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8766', commands :: [(Text, Text)]
commands = [("unicode-math","\\invlazys")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "most positive, INVERTED LAZY S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8767', commands :: [(Text, Text)]
commands = [("wasysym","\\AC"),("unicode-math","\\sinewave")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SINE WAVE, alternating current"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8768', commands :: [(Text, Text)]
commands = [("amssymb","\\wr"),("unicode-math","\\wr")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WREATH PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8769', commands :: [(Text, Text)]
commands = [("amssymb","\\nsim"),("wrisym","\\nsim"),("unicode-math","\\nsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8770', commands :: [(Text, Text)]
commands = [("amssymb","\\eqsim"),("unicode-math","\\eqsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equals, similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8771', commands :: [(Text, Text)]
commands = [("base","\\simeq"),("unicode-math","\\simeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "similar, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8772', commands :: [(Text, Text)]
commands = [("txfonts","\\nsimeq"),("unicode-math","\\nsime")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not similar, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8773', commands :: [(Text, Text)]
commands = [("base","\\cong"),("unicode-math","\\cong")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "congruent with"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8774', commands :: [(Text, Text)]
commands = [("unicode-math","\\simneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "similar, not equals [vert only for 9573 entity]"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8775', commands :: [(Text, Text)]
commands = [("amssymb","\\ncong"),("wrisym","\\ncong"),("unicode-math","\\ncong")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not congruent with"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8776', commands :: [(Text, Text)]
commands = [("base","\\approx"),("unicode-math","\\approx")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "approximate"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8777', commands :: [(Text, Text)]
commands = [("wrisym","\\napprox"),("unicode-math","\\napprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not approximate"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8778', commands :: [(Text, Text)]
commands = [("amssymb","\\approxeq"),("unicode-math","\\approxeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "approximate, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8779', commands :: [(Text, Text)]
commands = [("unicode-math","\\approxident")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "approximately identical to"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8780', commands :: [(Text, Text)]
commands = [("unicode-math","\\backcong")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ALL EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8781', commands :: [(Text, Text)]
commands = [("base","\\asymp"),("unicode-math","\\asymp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "asymptotically equal to"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8782', commands :: [(Text, Text)]
commands = [("amssymb","\\Bumpeq"),("wrisym","\\Bumpeq"),("unicode-math","\\Bumpeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "bumpy equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8783', commands :: [(Text, Text)]
commands = [("amssymb","\\bumpeq"),("wrisym","\\bumpeq"),("unicode-math","\\bumpeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "bumpy equals, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8784', commands :: [(Text, Text)]
commands = [("base","\\doteq"),("wrisym","\\dotequal"),("unicode-math","\\doteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equals, single dot above"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8785', commands :: [(Text, Text)]
commands = [("amssymb","\\Doteq"),("amssymb","\\doteqdot"),("unicode-math","\\Doteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "/doteq r: equals, even dots"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8786', commands :: [(Text, Text)]
commands = [("amssymb","\\fallingdotseq"),("unicode-math","\\fallingdotseq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equals, falling dots"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8787', commands :: [(Text, Text)]
commands = [("amssymb","\\risingdotseq"),("unicode-math","\\risingdotseq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equals, rising dots"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8788', commands :: [(Text, Text)]
commands = [("mathabx","\\coloneq"),("txfonts","\\coloneqq"),("unicode-math","\\coloneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\SetDelayed (wrisym), # := colon, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8789', commands :: [(Text, Text)]
commands = [("mathabx","\\eqcolon"),("txfonts","\\eqqcolon"),("unicode-math","\\eqcolon")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "# =:, equals, colon"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8790', commands :: [(Text, Text)]
commands = [("amssymb","\\eqcirc"),("unicode-math","\\eqcirc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "circle on equals sign"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8791', commands :: [(Text, Text)]
commands = [("amssymb","\\circeq"),("unicode-math","\\circeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "circle, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8792', commands :: [(Text, Text)]
commands = [("unicode-math","\\arceq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "arc, equals; CORRESPONDS TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8793', commands :: [(Text, Text)]
commands = [("mathabx","\\corresponds"),("oz","\\sdef"),("unicode-math","\\wedgeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "t \\Corresponds (marvosym), corresponds to (wedge over equals)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8794', commands :: [(Text, Text)]
commands = [("unicode-math","\\veeeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "logical or, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8795', commands :: [(Text, Text)]
commands = [("unicode-math","\\stareq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "STAR EQUALS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8796', commands :: [(Text, Text)]
commands = [("amssymb","\\triangleq"),("oz","\\varsdef"),("unicode-math","\\triangleq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "triangle, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8797', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqdef")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equals by definition"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8798', commands :: [(Text, Text)]
commands = [("unicode-math","\\measeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "MEASURED BY (m over equals)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8799', commands :: [(Text, Text)]
commands = [("unicode-math","\\questeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equal with questionmark"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8800', commands :: [(Text, Text)]
commands = [("base","\\neq"),("base","\\ne"),("unicode-math","\\ne")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "r: not equal"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8801', commands :: [(Text, Text)]
commands = [("base","\\equiv"),("unicode-math","\\equiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "identical with"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8802', commands :: [(Text, Text)]
commands = [("wrisym","\\nequiv"),("unicode-math","\\nequiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not identical with"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8803', commands :: [(Text, Text)]
commands = [("unicode-math","\\Equiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "strict equivalence (4 lines)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8804', commands :: [(Text, Text)]
commands = [("base","\\leq"),("base","\\le"),("unicode-math","\\leq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "r: less-than-or-equal"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8805', commands :: [(Text, Text)]
commands = [("base","\\geq"),("base","\\ge"),("unicode-math","\\geq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "r: greater-than-or-equal"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8806', commands :: [(Text, Text)]
commands = [("amssymb","\\leqq"),("unicode-math","\\leqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "less, double equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8807', commands :: [(Text, Text)]
commands = [("amssymb","\\geqq"),("unicode-math","\\geqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "greater, double equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8808', commands :: [(Text, Text)]
commands = [("amssymb","\\lneqq"),("unicode-math","\\lneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "less, not double equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8809', commands :: [(Text, Text)]
commands = [("amssymb","\\gneqq"),("unicode-math","\\gneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "greater, not double equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8810', commands :: [(Text, Text)]
commands = [("base","\\ll"),("unicode-math","\\ll")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "much less than, type 2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8811', commands :: [(Text, Text)]
commands = [("base","\\gg"),("unicode-math","\\gg")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "much greater than, type 2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8812', commands :: [(Text, Text)]
commands = [("amssymb","\\between"),("unicode-math","\\between")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "BETWEEN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8813', commands :: [(Text, Text)]
commands = [("mathabx","\\notasymp"),("wrisym","\\nasymp"),("unicode-math","\\nasymp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not asymptotically equal to"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8814', commands :: [(Text, Text)]
commands = [("amssymb","\\nless"),("unicode-math","\\nless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NOT LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8815', commands :: [(Text, Text)]
commands = [("amssymb","\\ngtr"),("unicode-math","\\ngtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NOT GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8816', commands :: [(Text, Text)]
commands = [("amssymb","\\nleq"),("wrisym","\\nleq"),("fourier","\\nleqslant"),("unicode-math","\\nleq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not less-than-or-equal"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8817', commands :: [(Text, Text)]
commands = [("amssymb","\\ngeq"),("wrisym","\\ngeq"),("fourier","\\ngeqslant"),("unicode-math","\\ngeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not greater-than-or-equal"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8818', commands :: [(Text, Text)]
commands = [("amssymb","\\lesssim"),("wasysym","\\apprle"),("unicode-math","\\lesssim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\LessTilde (wrisym), less, similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8819', commands :: [(Text, Text)]
commands = [("amssymb","\\gtrsim"),("wasysym","\\apprge"),("unicode-math","\\gtrsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "= \\GreaterTilde (wrisym), greater, similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8820', commands :: [(Text, Text)]
commands = [("wrisym","\\NotLessTilde"),("unicode-math","\\nlesssim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not less, similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8821', commands :: [(Text, Text)]
commands = [("wrisym","\\NotGreaterTilde"),("unicode-math","\\ngtrsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not greater, similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8822', commands :: [(Text, Text)]
commands = [("amssymb","\\lessgtr"),("unicode-math","\\lessgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "less, greater"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8823', commands :: [(Text, Text)]
commands = [("amssymb","\\gtrless"),("wrisym","\\GreaterLess"),("unicode-math","\\gtrless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "greater, less"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8824', commands :: [(Text, Text)]
commands = [("unicode-math","\\nlessgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not less, greater"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8825', commands :: [(Text, Text)]
commands = [("wrisym","\\NotGreaterLess"),("unicode-math","\\ngtrless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not greater, less"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8826', commands :: [(Text, Text)]
commands = [("base","\\prec"),("unicode-math","\\prec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PRECEDES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8827', commands :: [(Text, Text)]
commands = [("base","\\succ"),("unicode-math","\\succ")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8828', commands :: [(Text, Text)]
commands = [("amssymb","\\preccurlyeq"),("wrisym","\\PrecedesSlantEqual"),("unicode-math","\\preccurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "precedes, curly equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8829', commands :: [(Text, Text)]
commands = [("amssymb","\\succcurlyeq"),("wrisym","\\SucceedsSlantEqual"),("unicode-math","\\succcurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "succeeds, curly equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8830', commands :: [(Text, Text)]
commands = [("amssymb","\\precsim"),("wrisym","\\PrecedesTilde"),("unicode-math","\\precsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "precedes, similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8831', commands :: [(Text, Text)]
commands = [("amssymb","\\succsim"),("wrisym","\\SucceedsTilde"),("unicode-math","\\succsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "succeeds, similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8832', commands :: [(Text, Text)]
commands = [("amssymb","\\nprec"),("wrisym","\\nprec"),("unicode-math","\\nprec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not precedes"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8833', commands :: [(Text, Text)]
commands = [("amssymb","\\nsucc"),("wrisym","\\nsucc"),("unicode-math","\\nsucc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not succeeds"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8834', commands :: [(Text, Text)]
commands = [("base","\\subset"),("unicode-math","\\subset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "subset or is implied by"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8835', commands :: [(Text, Text)]
commands = [("base","\\supset"),("unicode-math","\\supset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "superset or implies"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8836', commands :: [(Text, Text)]
commands = [("wrisym","\\nsubset"),("unicode-math","\\nsubset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not subset, variant [slash negation]"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8837', commands :: [(Text, Text)]
commands = [("wrisym","\\nsupset"),("unicode-math","\\nsupset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not superset, variant [slash negation]"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8838', commands :: [(Text, Text)]
commands = [("base","\\subseteq"),("unicode-math","\\subseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "subset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8839', commands :: [(Text, Text)]
commands = [("base","\\supseteq"),("unicode-math","\\supseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "superset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8840', commands :: [(Text, Text)]
commands = [("amssymb","\\nsubseteq"),("wrisym","\\nsubseteq"),("unicode-math","\\nsubseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not subset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8841', commands :: [(Text, Text)]
commands = [("amssymb","\\nsupseteq"),("wrisym","\\nsupseteq"),("unicode-math","\\nsupseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not superset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8842', commands :: [(Text, Text)]
commands = [("amssymb","\\subsetneq"),("fourier","\\varsubsetneq"),("unicode-math","\\subsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "subset, not equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8843', commands :: [(Text, Text)]
commands = [("amssymb","\\supsetneq"),("unicode-math","\\supsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "superset, not equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8844', commands :: [(Text, Text)]
commands = [("unicode-math","\\cupleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTISET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8845', commands :: [(Text, Text)]
commands = [("unicode-math","\\cupdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "union, with dot"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8846', commands :: [(Text, Text)]
commands = [("base","\\uplus"),("oz","\\buni"),("unicode-math","\\uplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "plus sign in union"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8847', commands :: [(Text, Text)]
commands = [("amsfonts","\\sqsubset"),("unicode-math","\\sqsubset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "square subset"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8848', commands :: [(Text, Text)]
commands = [("amsfonts","\\sqsupset"),("unicode-math","\\sqsupset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "square superset"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8849', commands :: [(Text, Text)]
commands = [("base","\\sqsubseteq"),("unicode-math","\\sqsubseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "square subset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8850', commands :: [(Text, Text)]
commands = [("base","\\sqsupseteq"),("unicode-math","\\sqsupseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "square superset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8851', commands :: [(Text, Text)]
commands = [("base","\\sqcap"),("unicode-math","\\sqcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "square intersection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8852', commands :: [(Text, Text)]
commands = [("base","\\sqcup"),("unicode-math","\\sqcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "square union"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8853', commands :: [(Text, Text)]
commands = [("base","\\oplus"),("unicode-math","\\oplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "plus sign in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8854', commands :: [(Text, Text)]
commands = [("base","\\ominus"),("unicode-math","\\ominus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "minus sign in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8855', commands :: [(Text, Text)]
commands = [("base","\\otimes"),("unicode-math","\\otimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "multiply sign in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8856', commands :: [(Text, Text)]
commands = [("base","\\oslash"),("unicode-math","\\oslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "solidus in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8857', commands :: [(Text, Text)]
commands = [("base","\\odot"),("unicode-math","\\odot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "middle dot in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8858', commands :: [(Text, Text)]
commands = [("amssymb","\\circledcirc"),("unicode-math","\\circledcirc")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "small circle in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8859', commands :: [(Text, Text)]
commands = [("amssymb","\\circledast"),("unicode-math","\\circledast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "asterisk in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8860', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledequal")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "equal in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8861', commands :: [(Text, Text)]
commands = [("amssymb","\\circleddash"),("unicode-math","\\circleddash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "hyphen in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8862', commands :: [(Text, Text)]
commands = [("amssymb","\\boxplus"),("unicode-math","\\boxplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "plus sign in box"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8863', commands :: [(Text, Text)]
commands = [("amssymb","\\boxminus"),("unicode-math","\\boxminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "minus sign in box"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8864', commands :: [(Text, Text)]
commands = [("amssymb","\\boxtimes"),("unicode-math","\\boxtimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "multiply sign in box"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8865', commands :: [(Text, Text)]
commands = [("amssymb","\\boxdot"),("stmaryrd","\\boxdot"),("unicode-math","\\boxdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "/dotsquare /boxdot b: small dot in box"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8866', commands :: [(Text, Text)]
commands = [("base","\\vdash"),("unicode-math","\\vdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHT TACK, proves, implies, yields, (vertical, dash)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8867', commands :: [(Text, Text)]
commands = [("amssymb","\\dashv"),("unicode-math","\\dashv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT TACK, non-theorem, does not yield, (dash, vertical)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8868', commands :: [(Text, Text)]
commands = [("base","\\top"),("unicode-math","\\top")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWN TACK, top"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8869', commands :: [(Text, Text)]
commands = [("base","\\bot"),("unicode-math","\\bot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UP TACK, bottom"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8870', commands :: [(Text, Text)]
commands = [("base","\\vdash"),("unicode-math","\\assert")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ASSERTION (vertical, short dash)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8871', commands :: [(Text, Text)]
commands = [("base","\\models"),("unicode-math","\\models")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "MODELS (vertical, short double dash)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8872', commands :: [(Text, Text)]
commands = [("amssymb","\\vDash"),("fourier","\\vDash"),("unicode-math","\\vDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TRUE (vertical, double dash)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8873', commands :: [(Text, Text)]
commands = [("amssymb","\\Vdash"),("unicode-math","\\Vdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "double vertical, dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8874', commands :: [(Text, Text)]
commands = [("amssymb","\\Vvdash"),("unicode-math","\\Vvdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "triple vertical, dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8875', commands :: [(Text, Text)]
commands = [("mathabx","\\VDash"),("txfonts","\\VDash"),("unicode-math","\\VDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "double vert, double dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8876', commands :: [(Text, Text)]
commands = [("amssymb","\\nvdash"),("unicode-math","\\nvdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not vertical, dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8877', commands :: [(Text, Text)]
commands = [("amssymb","\\nvDash"),("fourier","\\nvDash"),("unicode-math","\\nvDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not vertical, double dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8878', commands :: [(Text, Text)]
commands = [("amssymb","\\nVdash"),("unicode-math","\\nVdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not double vertical, dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8879', commands :: [(Text, Text)]
commands = [("amssymb","\\nVDash"),("unicode-math","\\nVDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not double vert, double dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8880', commands :: [(Text, Text)]
commands = [("unicode-math","\\prurel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "element PRECEDES UNDER RELATION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8881', commands :: [(Text, Text)]
commands = [("unicode-math","\\scurel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS UNDER RELATION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8882', commands :: [(Text, Text)]
commands = [("amssymb","\\vartriangleleft"),("unicode-math","\\vartriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left triangle, open, variant"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8883', commands :: [(Text, Text)]
commands = [("amssymb","\\vartriangleright"),("unicode-math","\\vartriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right triangle, open, variant"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8884', commands :: [(Text, Text)]
commands = [("amssymb","\\trianglelefteq"),("wrisym","\\unlhd"),("unicode-math","\\trianglelefteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left triangle, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8885', commands :: [(Text, Text)]
commands = [("amssymb","\\trianglerighteq"),("wrisym","\\unrhd"),("unicode-math","\\trianglerighteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right triangle, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8886', commands :: [(Text, Text)]
commands = [("txfonts","\\multimapdotbothA"),("unicode-math","\\origof")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ORIGINAL OF"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8887', commands :: [(Text, Text)]
commands = [("txfonts","\\multimapdotbothB"),("unicode-math","\\imageof")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "IMAGE OF"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8888', commands :: [(Text, Text)]
commands = [("amssymb","\\multimap"),("unicode-math","\\multimap")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "/MULTIMAP a:"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8889', commands :: [(Text, Text)]
commands = [("unicode-math","\\hermitmatrix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HERMITIAN CONJUGATE MATRIX"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8890', commands :: [(Text, Text)]
commands = [("amssymb","\\intercal"),("fourier","\\intercal"),("unicode-math","\\intercal")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "intercal"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8891', commands :: [(Text, Text)]
commands = [("amssymb","\\veebar"),("unicode-math","\\veebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "logical or, bar below (large vee); exclusive disjunction"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8892', commands :: [(Text, Text)]
commands = [("amssymb","\\barwedge"),("unicode-math","\\barwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "logical NAND (bar over wedge)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8893', commands :: [(Text, Text)]
commands = [("unicode-math","\\barvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "bar, vee (large vee)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8894', commands :: [(Text, Text)]
commands = [("unicode-math","\\measuredrightangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "right angle-measured [with arc]"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8895', commands :: [(Text, Text)]
commands = [("unicode-math","\\varlrtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8896', commands :: [(Text, Text)]
commands = [("base","\\bigwedge"),("unicode-math","\\bigwedge")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "logical or operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8897', commands :: [(Text, Text)]
commands = [("base","\\bigvee"),("unicode-math","\\bigvee")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "logical and operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8898', commands :: [(Text, Text)]
commands = [("base","\\bigcap"),("oz","\\dint"),("unicode-math","\\bigcap")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "\\dinter (oz), intersection operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8899', commands :: [(Text, Text)]
commands = [("base","\\bigcup"),("oz","\\duni"),("unicode-math","\\bigcup")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "\\dunion (oz), union operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8900', commands :: [(Text, Text)]
commands = [("base","\\diamond"),("unicode-math","\\smwhtdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DIAMOND OPERATOR (white diamond)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8901', commands :: [(Text, Text)]
commands = [("base","\\cdot"),("unicode-math","\\cdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOT OPERATOR (small middle dot)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8902', commands :: [(Text, Text)]
commands = [("base","\\star"),("unicode-math","\\star")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "small star, filled, low"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8903', commands :: [(Text, Text)]
commands = [("amssymb","\\divideontimes"),("unicode-math","\\divideontimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "division on times"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8904', commands :: [(Text, Text)]
commands = [("base","\\bowtie"),("txfonts","\\lrtimes"),("unicode-math","\\bowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "BOWTIE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8905', commands :: [(Text, Text)]
commands = [("amssymb","\\ltimes"),("unicode-math","\\ltimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "times sign, left closed"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8906', commands :: [(Text, Text)]
commands = [("amssymb","\\rtimes"),("unicode-math","\\rtimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "times sign, right closed"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8907', commands :: [(Text, Text)]
commands = [("amssymb","\\leftthreetimes"),("unicode-math","\\leftthreetimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LEFT SEMIDIRECT PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8908', commands :: [(Text, Text)]
commands = [("amssymb","\\rightthreetimes"),("unicode-math","\\rightthreetimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "RIGHT SEMIDIRECT PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8909', commands :: [(Text, Text)]
commands = [("amssymb","\\backsimeq"),("unicode-math","\\backsimeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "reverse similar, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8910', commands :: [(Text, Text)]
commands = [("amssymb","\\curlyvee"),("unicode-math","\\curlyvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CURLY LOGICAL OR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8911', commands :: [(Text, Text)]
commands = [("amssymb","\\curlywedge"),("unicode-math","\\curlywedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CURLY LOGICAL AND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8912', commands :: [(Text, Text)]
commands = [("amssymb","\\Subset"),("unicode-math","\\Subset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8913', commands :: [(Text, Text)]
commands = [("amssymb","\\Supset"),("unicode-math","\\Supset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE SUPERSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8914', commands :: [(Text, Text)]
commands = [("amssymb","\\Cap"),("unicode-math","\\Cap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "/cap /doublecap b: DOUBLE INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8915', commands :: [(Text, Text)]
commands = [("amssymb","\\Cup"),("unicode-math","\\Cup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "/cup /doublecup b: DOUBLE UNION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8916', commands :: [(Text, Text)]
commands = [("amssymb","\\pitchfork"),("unicode-math","\\pitchfork")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PITCHFORK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8917', commands :: [(Text, Text)]
commands = [("mathabx","\\hash"),("unicode-math","\\equalparallel")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "parallel, equal; equal or parallel"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8918', commands :: [(Text, Text)]
commands = [("amssymb","\\lessdot"),("unicode-math","\\lessdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "less than, with dot"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8919', commands :: [(Text, Text)]
commands = [("amssymb","\\gtrdot"),("unicode-math","\\gtrdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "greater than, with dot"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8920', commands :: [(Text, Text)]
commands = [("amssymb","\\lll"),("unicode-math","\\lll")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "triple less-than"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8921', commands :: [(Text, Text)]
commands = [("amssymb","\\ggg"),("unicode-math","\\ggg")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "triple greater-than"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8922', commands :: [(Text, Text)]
commands = [("amssymb","\\lesseqgtr"),("unicode-math","\\lesseqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "less, equals, greater"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8923', commands :: [(Text, Text)]
commands = [("amssymb","\\gtreqless"),("unicode-math","\\gtreqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "greater, equals, less"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8924', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equal-or-less"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8925', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "equal-or-greater"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8926', commands :: [(Text, Text)]
commands = [("amssymb","\\curlyeqprec"),("unicode-math","\\curlyeqprec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "curly equals, precedes"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8927', commands :: [(Text, Text)]
commands = [("amssymb","\\curlyeqsucc"),("unicode-math","\\curlyeqsucc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "curly equals, succeeds"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8928', commands :: [(Text, Text)]
commands = [("amssymb","\\npreceq"),("wrisym","\\npreceq"),("unicode-math","\\npreccurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOES NOT PRECEDE OR EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8929', commands :: [(Text, Text)]
commands = [("amssymb","\\nsucceq"),("wrisym","\\nsucceq"),("unicode-math","\\nsucccurlyeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not succeeds, curly equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8930', commands :: [(Text, Text)]
commands = [("wrisym","\\nsqsubseteq"),("unicode-math","\\nsqsubseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not, square subset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8931', commands :: [(Text, Text)]
commands = [("wrisym","\\nsqsupseteq"),("unicode-math","\\nsqsupseteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not, square superset, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8932', commands :: [(Text, Text)]
commands = [("unicode-math","\\sqsubsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "square subset, not equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8933', commands :: [(Text, Text)]
commands = [("unicode-math","\\sqsupsetneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "square superset, not equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8934', commands :: [(Text, Text)]
commands = [("amssymb","\\lnsim"),("unicode-math","\\lnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "less, not similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8935', commands :: [(Text, Text)]
commands = [("amssymb","\\gnsim"),("unicode-math","\\gnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "greater, not similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8936', commands :: [(Text, Text)]
commands = [("amssymb","\\precnsim"),("unicode-math","\\precnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "precedes, not similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8937', commands :: [(Text, Text)]
commands = [("amssymb","\\succnsim"),("unicode-math","\\succnsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "succeeds, not similar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8938', commands :: [(Text, Text)]
commands = [("amssymb","\\ntriangleleft"),("wrisym","\\NotLeftTriangle"),("unicode-math","\\ntriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not left triangle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8939', commands :: [(Text, Text)]
commands = [("amssymb","\\ntriangleright"),("wrisym","\\NotRightTriangle"),("unicode-math","\\ntriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not right triangle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8940', commands :: [(Text, Text)]
commands = [("amssymb","\\ntrianglelefteq"),("wrisym","\\nunlhd"),("unicode-math","\\ntrianglelefteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not left triangle, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8941', commands :: [(Text, Text)]
commands = [("amssymb","\\ntrianglerighteq"),("wrisym","\\nunrhd"),("unicode-math","\\ntrianglerighteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "not right triangle, equals"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8942', commands :: [(Text, Text)]
commands = [("base","\\vdots"),("unicode-math","\\vdots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "VERTICAL ELLIPSIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8943', commands :: [(Text, Text)]
commands = [("base","\\cdots"),("unicode-math","\\unicodecdots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "three dots, centered"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8944', commands :: [(Text, Text)]
commands = [("mathdots","\\iddots"),("yhmath","\\adots"),("unicode-math","\\adots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "three dots, ascending"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8945', commands :: [(Text, Text)]
commands = [("base","\\ddots"),("unicode-math","\\ddots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "three dots, descending"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8946', commands :: [(Text, Text)]
commands = [("unicode-math","\\disin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF WITH LONG HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8947', commands :: [(Text, Text)]
commands = [("unicode-math","\\varisins")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8948', commands :: [(Text, Text)]
commands = [("unicode-math","\\isins")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SMALL ELEMENT OF WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8949', commands :: [(Text, Text)]
commands = [("unicode-math","\\isindot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8950', commands :: [(Text, Text)]
commands = [("mathabx","\\barin"),("unicode-math","\\varisinobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8951', commands :: [(Text, Text)]
commands = [("unicode-math","\\isinobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SMALL ELEMENT OF WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8952', commands :: [(Text, Text)]
commands = [("unicode-math","\\isinvb")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8953', commands :: [(Text, Text)]
commands = [("unicode-math","\\isinE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF WITH TWO HORIZONTAL STROKES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8954', commands :: [(Text, Text)]
commands = [("unicode-math","\\nisd")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CONTAINS WITH LONG HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8955', commands :: [(Text, Text)]
commands = [("unicode-math","\\varnis")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CONTAINS WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8956', commands :: [(Text, Text)]
commands = [("unicode-math","\\nis")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SMALL CONTAINS WITH VERTICAL BAR AT END OF HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8957', commands :: [(Text, Text)]
commands = [("unicode-math","\\varniobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CONTAINS WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8958', commands :: [(Text, Text)]
commands = [("unicode-math","\\niobar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SMALL CONTAINS WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8959', commands :: [(Text, Text)]
commands = [("base","\\mathsf{E}"),("unicode-math","\\bagmember")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "Z NOTATION BAG MEMBERSHIP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8960', commands :: [(Text, Text)]
commands = [("mathabx","\\diameter"),("amssymb","\\varnothing"),("unicode-math","\\diameter")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIAMETER SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8962', commands :: [(Text, Text)]
commands = [("unicode-math","\\house")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HOUSE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8965', commands :: [(Text, Text)]
commands = [("amssymb","\\barwedge"),("unicode-math","\\varbarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PROJECTIVE (bar over small wedge) not nand"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8966', commands :: [(Text, Text)]
commands = [("amssymb","\\doublebarwedge"),("unicode-math","\\vardoublebarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PERSPECTIVE (double bar over small wedge)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8968', commands :: [(Text, Text)]
commands = [("base","\\lceil"),("unicode-math","\\lceil")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT CEILING"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8969', commands :: [(Text, Text)]
commands = [("base","\\rceil"),("unicode-math","\\rceil")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT CEILING"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8970', commands :: [(Text, Text)]
commands = [("base","\\lfloor"),("unicode-math","\\lfloor")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT FLOOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8971', commands :: [(Text, Text)]
commands = [("base","\\rfloor"),("unicode-math","\\rfloor")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT FLOOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8976', commands :: [(Text, Text)]
commands = [("wasysym","\\invneg"),("unicode-math","\\invnot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "reverse not"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8977', commands :: [(Text, Text)]
commands = [("wasysym","\\wasylozenge"),("unicode-math","\\sqlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE LOZENGE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8978', commands :: [(Text, Text)]
commands = [("unicode-math","\\profline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "profile of a line"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8979', commands :: [(Text, Text)]
commands = [("unicode-math","\\profsurf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "profile of a surface"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8983', commands :: [(Text, Text)]
commands = [("unicode-math","\\viewdata")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "VIEWDATA SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8985', commands :: [(Text, Text)]
commands = [("unicode-math","\\turnednot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TURNED NOT SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8988', commands :: [(Text, Text)]
commands = [("amsfonts","\\ulcorner"),("unicode-math","\\ulcorner")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "upper left corner"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8989', commands :: [(Text, Text)]
commands = [("amsfonts","\\urcorner"),("unicode-math","\\urcorner")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "upper right corner"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8990', commands :: [(Text, Text)]
commands = [("amsfonts","\\llcorner"),("unicode-math","\\llcorner")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "lower left corner"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8991', commands :: [(Text, Text)]
commands = [("amsfonts","\\lrcorner"),("unicode-math","\\lrcorner")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "lower right corner"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8992', commands :: [(Text, Text)]
commands = [("unicode-math","\\inttop")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TOP HALF INTEGRAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8993', commands :: [(Text, Text)]
commands = [("unicode-math","\\intbottom")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BOTTOM HALF INTEGRAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8994', commands :: [(Text, Text)]
commands = [("base","\\frown"),("base","\\smallfrown"),("unicode-math","\\frown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "FROWN (down curve)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\8995', commands :: [(Text, Text)]
commands = [("base","\\smile"),("base","\\smallsmile"),("unicode-math","\\smile")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SMILE (up curve)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9001', commands :: [(Text, Text)]
commands = [("base","\\langle"),("unicode","\\langle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "Left angle bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9002', commands :: [(Text, Text)]
commands = [("base","\\rangle"),("unicode","\\rangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "Right angle bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9004', commands :: [(Text, Text)]
commands = [("unicode-math","\\varhexagonlrbonds")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "six carbon ring, corner down, double bonds lower right etc"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9010', commands :: [(Text, Text)]
commands = [("unicode-math","\\conictaper")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CONICAL TAPER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9014', commands :: [(Text, Text)]
commands = [("unicode-math","\\topbot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL I-BEAM, top and bottom"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9015', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL SQUISH QUAD"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9016', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9017', commands :: [(Text, Text)]
commands = [("wasysym","\\APLinv")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD DIVIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9018', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9019', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD JOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9020', commands :: [(Text, Text)]
commands = [("wasysym","\\APLcirc{\\APLbox}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9021', commands :: [(Text, Text)]
commands = [("wasysym","\\APLvert{\\Circle}"),("unicode-math","\\obar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "x \\obar (stmaryrd), APL FUNCTIONAL SYMBOL CIRCLE STILE, circle with vertical bar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9022', commands :: [(Text, Text)]
commands = [("wasysym","\\APLcirc{\\Circle}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL CIRCLE JOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9023', commands :: [(Text, Text)]
commands = [("wasysym","\\notslash"),("unicode-math","\\APLnotslash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "APL FUNCTIONAL SYMBOL SLASH BAR, solidus, bar through"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9024', commands :: [(Text, Text)]
commands = [("wasysym","\\notbackslash"),("unicode-math","\\APLnotbackslash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL BACKSLASH BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9025', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD SLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9026', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD BACKSLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9027', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9028', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9029', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL LEFTWARDS VANE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9030', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL RIGHTWARDS VANE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9031', commands :: [(Text, Text)]
commands = [("wasysym","\\APLleftarrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9032', commands :: [(Text, Text)]
commands = [("wasysym","\\APLrightarrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9033', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL CIRCLE BACKSLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9034', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DOWN TACK UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9035', commands :: [(Text, Text)]
commands = [("wasysym","\\APLvert{\\APLup}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DELTA STILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9036', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD DOWN CARET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9037', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9038', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DOWN TACK JOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9039', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL UPWARDS VANE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9040', commands :: [(Text, Text)]
commands = [("wasysym","\\APLuparrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD UPWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9041', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL UP TACK OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9042', commands :: [(Text, Text)]
commands = [("wasysym","\\APLvert{\\APLdown}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DEL STILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9043', commands :: [(Text, Text)]
commands = [("unicode-math","\\APLboxupcaret")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD UP CARET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9044', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD DEL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9045', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL UP TACK JOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9046', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DOWNWARDS VANE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9047', commands :: [(Text, Text)]
commands = [("wasysym","\\APLdownarrowbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD DOWNWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9048', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUOTE UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9049', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DELTA UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9050', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DIAMOND UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9051', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL JOT UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9052', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL CIRCLE UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9053', commands :: [(Text, Text)]
commands = [("wasysym","\\APLcomment")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL UP SHOE JOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9054', commands :: [(Text, Text)]
commands = [("wasysym","\\APLinput")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUOTE QUAD"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9055', commands :: [(Text, Text)]
commands = [("wasysym","\\APLlog")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL CIRCLE STAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9056', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD COLON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9057', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL UP TACK DIAERESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9058', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DEL DIAERESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9059', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL STAR DIAERESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9060', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL JOT DIAERESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9061', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL CIRCLE DIAERESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9062', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DOWN SHOE STILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9063', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL LEFT SHOE STILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9064', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL TILDE DIAERESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9065', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL GREATER-THAN DIAERESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9066', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL COMMA BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9067', commands :: [(Text, Text)]
commands = [("wasysym","\\APLnot{\\APLdown}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DEL TILDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9068', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL ZILDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9069', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL STILE TILDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9070', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL SEMICOLON UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9071', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD NOT EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9072', commands :: [(Text, Text)]
commands = [("unicode-math","\\APLboxquestion")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL QUAD QUESTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9073', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL DOWN CARET TILDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9074', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL UP CARET TILDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9075', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9076', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9077', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9078', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL ALPHA UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9079', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL EPSILON UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9080', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL IOTA UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9081', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "APL FUNCTIONAL SYMBOL OMEGA UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9084', commands :: [(Text, Text)]
commands = [("unicode-math","\\rangledownzigzagarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT ANGLE WITH DOWNWARDS ZIGZAG ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9108', commands :: [(Text, Text)]
commands = [("unicode-math","\\hexagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "horizontal benzene ring [hexagon flat open]"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9115', commands :: [(Text, Text)]
commands = [("unicode-math","\\lparenuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT PARENTHESIS UPPER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9116', commands :: [(Text, Text)]
commands = [("unicode-math","\\lparenextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT PARENTHESIS EXTENSION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9117', commands :: [(Text, Text)]
commands = [("unicode-math","\\lparenlend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT PARENTHESIS LOWER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9118', commands :: [(Text, Text)]
commands = [("unicode-math","\\rparenuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT PARENTHESIS UPPER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9119', commands :: [(Text, Text)]
commands = [("unicode-math","\\rparenextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT PARENTHESIS EXTENSION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9120', commands :: [(Text, Text)]
commands = [("unicode-math","\\rparenlend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT PARENTHESIS LOWER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9121', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbrackuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT SQUARE BRACKET UPPER CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9122', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbrackextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT SQUARE BRACKET EXTENSION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9123', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbracklend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT SQUARE BRACKET LOWER CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9124', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbrackuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT SQUARE BRACKET UPPER CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9125', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbrackextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT SQUARE BRACKET EXTENSION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9126', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbracklend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT SQUARE BRACKET LOWER CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9127', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbraceuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT CURLY BRACKET UPPER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9128', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbracemid")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT CURLY BRACKET MIDDLE PIECE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9129', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbracelend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT CURLY BRACKET LOWER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9130', commands :: [(Text, Text)]
commands = [("unicode-math","\\vbraceextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CURLY BRACKET EXTENSION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9131', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbraceuend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT CURLY BRACKET UPPER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9132', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbracemid")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT CURLY BRACKET MIDDLE PIECE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9133', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbracelend")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT CURLY BRACKET LOWER HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9134', commands :: [(Text, Text)]
commands = [("unicode-math","\\intextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INTEGRAL EXTENSION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9135', commands :: [(Text, Text)]
commands = [("unicode-math","\\harrowextender")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HORIZONTAL LINE EXTENSION (used to extend arrows)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9136', commands :: [(Text, Text)]
commands = [("unicode-math","\\lmoustache")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "? \\lmoustache, UPPER LEFT OR LOWER RIGHT CURLY BRACKET SECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9137', commands :: [(Text, Text)]
commands = [("unicode-math","\\rmoustache")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "? \\rmoustache, UPPER RIGHT OR LOWER LEFT CURLY BRACKET SECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9138', commands :: [(Text, Text)]
commands = [("unicode-math","\\sumtop")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUMMATION TOP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9139', commands :: [(Text, Text)]
commands = [("unicode-math","\\sumbottom")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUMMATION BOTTOM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9140', commands :: [(Text, Text)]
commands = [("unicode-math","\\overbracket")], category :: TeXSymbolType
category = TeXSymbolType
TOver, comments :: Text
comments = "TOP SQUARE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9141', commands :: [(Text, Text)]
commands = [("unicode-math","\\underbracket")], category :: TeXSymbolType
category = TeXSymbolType
TUnder, comments :: Text
comments = "BOTTOM SQUARE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9142', commands :: [(Text, Text)]
commands = [("unicode-math","\\bbrktbrk")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BOTTOM SQUARE BRACKET OVER TOP SQUARE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9143', commands :: [(Text, Text)]
commands = [("unicode-math","\\sqrtbottom")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RADICAL SYMBOL BOTTOM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9144', commands :: [(Text, Text)]
commands = [("unicode-math","\\lvboxline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT VERTICAL BOX LINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9145', commands :: [(Text, Text)]
commands = [("unicode-math","\\rvboxline")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT VERTICAL BOX LINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9166', commands :: [(Text, Text)]
commands = [("unicode-math","\\varcarriagereturn")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RETURN SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9168', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "VERTICAL LINE EXTENSION (VERTICAL LINE EXTENSION)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9180', commands :: [(Text, Text)]
commands = [("wrisym","\\overparen"),("yhmath mathabx fourier","\\wideparen"),("unicode-math","\\overparen")], category :: TeXSymbolType
category = TeXSymbolType
TOver, comments :: Text
comments = "TOP PARENTHESIS (mathematical use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9181', commands :: [(Text, Text)]
commands = [("wrisym","\\underparen"),("unicode-math","\\underparen")], category :: TeXSymbolType
category = TeXSymbolType
TUnder, comments :: Text
comments = "BOTTOM PARENTHESIS (mathematical use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9182', commands :: [(Text, Text)]
commands = [("base","\\overbrace"),("unicode-math","\\overbrace")], category :: TeXSymbolType
category = TeXSymbolType
TOver, comments :: Text
comments = "TOP CURLY BRACKET (mathematical use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9183', commands :: [(Text, Text)]
commands = [("base","\\underbrace"),("unicode-math","\\underbrace")], category :: TeXSymbolType
category = TeXSymbolType
TUnder, comments :: Text
comments = "BOTTOM CURLY BRACKET (mathematical use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9184', commands :: [(Text, Text)]
commands = [("unicode-math","\\obrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TOP TORTOISE SHELL BRACKET (mathematical use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9185', commands :: [(Text, Text)]
commands = [("unicode-math","\\ubrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BOTTOM TORTOISE SHELL BRACKET (mathematical use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9186', commands :: [(Text, Text)]
commands = [("unicode-math","\\trapezium")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE TRAPEZIUM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9187', commands :: [(Text, Text)]
commands = [("unicode-math","\\benzenr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BENZENE RING WITH CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9188', commands :: [(Text, Text)]
commands = [("unicode-math","\\strns")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "STRAIGHTNESS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9189', commands :: [(Text, Text)]
commands = [("unicode-math","\\fltns")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FLATNESS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9190', commands :: [(Text, Text)]
commands = [("wasysym","\\AC"),("unicode-math","\\accurrent")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "AC CURRENT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9191', commands :: [(Text, Text)]
commands = [("unicode-math","\\elinters")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ELECTRICAL INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9416', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "oS capital S in circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9478', commands :: [(Text, Text)]
commands = [("unicode-math","\\bdtriplevdash")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "doubly broken vert"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9600', commands :: [(Text, Text)]
commands = [("unicode-math","\\blockuphalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPPER HALF BLOCK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9604', commands :: [(Text, Text)]
commands = [("unicode-math","\\blocklowhalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER HALF BLOCK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9608', commands :: [(Text, Text)]
commands = [("unicode-math","\\blockfull")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULL BLOCK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9612', commands :: [(Text, Text)]
commands = [("unicode-math","\\blocklefthalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT HALF BLOCK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9616', commands :: [(Text, Text)]
commands = [("unicode-math","\\blockrighthalf")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT HALF BLOCK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9617', commands :: [(Text, Text)]
commands = [("unicode-math","\\blockqtrshaded")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "25\\% shaded block"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9618', commands :: [(Text, Text)]
commands = [("unicode-math","\\blockhalfshaded")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "50\\% shaded block"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9619', commands :: [(Text, Text)]
commands = [("unicode-math","\\blockthreeqtrshaded")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "75\\% shaded block"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9632', commands :: [(Text, Text)]
commands = [("base","\\blacksquare"),("unicode-math","\\mdlgblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9633', commands :: [(Text, Text)]
commands = [("base","\\square"),("unicode-math","\\mdlgwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9634', commands :: [(Text, Text)]
commands = [("unicode-math","\\squoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SQUARE WITH ROUNDED CORNERS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9635', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackinwhitesquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SQUARE CONTAINING BLACK SMALL SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9636', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarehfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, horizontal rule filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9637', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarevfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, vertical rule filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9638', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarehvfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE WITH ORTHOGONAL CROSSHATCH FILL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9639', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarenwsefill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, nw-to-se rule filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9640', commands :: [(Text, Text)]
commands = [("unicode-math","\\squareneswfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, ne-to-sw rule filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9641', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarecrossfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE WITH DIAGONAL CROSSHATCH FILL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9642', commands :: [(Text, Text)]
commands = [("unicode-math","\\smblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "sq bullet, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9643', commands :: [(Text, Text)]
commands = [("unicode-math","\\smwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SMALL SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9644', commands :: [(Text, Text)]
commands = [("unicode-math","\\hrectangleblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK RECTANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9645', commands :: [(Text, Text)]
commands = [("unicode-math","\\hrectangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "horizontal rectangle, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9646', commands :: [(Text, Text)]
commands = [("unicode-math","\\vrectangleblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK VERTICAL RECTANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9647', commands :: [(Text, Text)]
commands = [("unicode-math","\\vrectangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "rectangle, white (vertical)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9648', commands :: [(Text, Text)]
commands = [("unicode-math","\\parallelogramblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK PARALLELOGRAM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9649', commands :: [(Text, Text)]
commands = [("unicode-math","\\parallelogram")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "parallelogram, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9650', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigblacktriangleup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK UP-POINTING TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9651', commands :: [(Text, Text)]
commands = [("base","\\bigtriangleup"),("amsfonts","\\triangle"),("unicode-math","\\bigtriangleup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "# \\vartriangle (amssymb), big up triangle, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9652', commands :: [(Text, Text)]
commands = [("mathabx","\\blacktriangleup"),("unicode-math","\\blacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "up triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9653', commands :: [(Text, Text)]
commands = [("mathabx","\\smalltriangleup"),("amssymb","\\vartriangle"),("unicode-math","\\vartriangle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "small up triangle, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9654', commands :: [(Text, Text)]
commands = [("wasysym","\\RHD"),("fourier -mathabx","\\blacktriangleright"),("unicode-math","\\blacktriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "(large) right triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9655', commands :: [(Text, Text)]
commands = [("amssymb","\\rhd"),("wasysym","\\rhd"),("oz","\\rres"),("unicode-math","\\triangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "= \\RightTriangle (wrisym), (large) right triangle, open; z notation range restriction"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9656', commands :: [(Text, Text)]
commands = [("mathabx","\\blacktriangleright"),("unicode-math","\\smallblacktriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "right triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9657', commands :: [(Text, Text)]
commands = [("mathabx","\\smalltriangleright"),("base","\\triangleright"),("unicode-math","\\smalltriangleright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "x \\triangleright (mathabx), right triangle, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9658', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackpointerright")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK RIGHT-POINTING POINTER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9659', commands :: [(Text, Text)]
commands = [("mathabx","\\triangleright"),("unicode-math","\\whitepointerright")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE RIGHT-POINTING POINTER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9660', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigblacktriangledown")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "big down triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9661', commands :: [(Text, Text)]
commands = [("base","\\bigtriangledown"),("unicode-math","\\bigtriangledown")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "big down triangle, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9662', commands :: [(Text, Text)]
commands = [("mathabx","\\blacktriangledown"),("unicode-math","\\blacktriangledown")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "BLACK DOWN-POINTING SMALL TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9663', commands :: [(Text, Text)]
commands = [("mathabx","\\smalltriangledown"),("amssymb","\\triangledown"),("unicode-math","\\triangledown")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE DOWN-POINTING SMALL TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9664', commands :: [(Text, Text)]
commands = [("wasysym","\\LHD"),("fourier -mathabx","\\blacktriangleleft"),("unicode-math","\\blacktriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "(large) left triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9665', commands :: [(Text, Text)]
commands = [("amssymb","\\lhd"),("wasysym","\\lhd"),("oz","\\dres"),("unicode-math","\\triangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "= \\LeftTriangle (wrisym), (large) left triangle, open; z notation domain restriction"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9666', commands :: [(Text, Text)]
commands = [("mathabx","\\blacktriangleleft"),("unicode-math","\\smallblacktriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "left triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9667', commands :: [(Text, Text)]
commands = [("mathabx","\\smalltriangleleft"),("base","\\triangleleft"),("unicode-math","\\smalltriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "x \\triangleleft (mathabx), left triangle, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9668', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackpointerleft")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK LEFT-POINTING POINTER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9669', commands :: [(Text, Text)]
commands = [("mathabx","\\triangleleft"),("unicode-math","\\whitepointerleft")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE LEFT-POINTING POINTER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9670', commands :: [(Text, Text)]
commands = [("txfonts","\\Diamondblack"),("unicode-math","\\mdlgblkdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9671', commands :: [(Text, Text)]
commands = [("amssymb","\\Diamond"),("unicode-math","\\mdlgwhtdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE DIAMOND; diamond, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9672', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackinwhitediamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE DIAMOND CONTAINING BLACK SMALL DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9673', commands :: [(Text, Text)]
commands = [("unicode-math","\\fisheye")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FISHEYE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9674', commands :: [(Text, Text)]
commands = [("amssymb","\\lozenge"),("unicode-math","\\mdlgwhtlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOZENGE or total mark"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9675', commands :: [(Text, Text)]
commands = [("wasysym","\\Circle"),("unicode-math","\\mdlgwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "medium large circle"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9676', commands :: [(Text, Text)]
commands = [("unicode-math","\\dottedcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOTTED CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9677', commands :: [(Text, Text)]
commands = [("unicode-math","\\circlevertfill")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLE WITH VERTICAL FILL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9678', commands :: [(Text, Text)]
commands = [("amssymb","\\circledcirc"),("unicode-math","\\bullseye")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BULLSEYE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9679', commands :: [(Text, Text)]
commands = [("wasysym","\\CIRCLE"),("unicode-math","\\mdlgblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "circle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9680', commands :: [(Text, Text)]
commands = [("wasysym","\\LEFTcircle"),("unicode-math","\\circlelefthalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "circle, filled left half [harvey ball]"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9681', commands :: [(Text, Text)]
commands = [("wasysym","\\RIGHTcircle"),("unicode-math","\\circlerighthalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "circle, filled right half"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9682', commands :: [(Text, Text)]
commands = [("unicode-math","\\circlebottomhalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "circle, filled bottom half"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9683', commands :: [(Text, Text)]
commands = [("unicode-math","\\circletophalfblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "circle, filled top half"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9684', commands :: [(Text, Text)]
commands = [("unicode-math","\\circleurquadblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLE WITH UPPER RIGHT QUADRANT BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9685', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackcircleulquadwhite")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLE WITH ALL BUT UPPER LEFT QUADRANT BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9686', commands :: [(Text, Text)]
commands = [("wasysym","\\LEFTCIRCLE"),("unicode-math","\\blacklefthalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT HALF BLACK CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9687', commands :: [(Text, Text)]
commands = [("wasysym","\\RIGHTCIRCLE"),("unicode-math","\\blackrighthalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT HALF BLACK CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9688', commands :: [(Text, Text)]
commands = [("unicode-math","\\inversebullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INVERSE BULLET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9689', commands :: [(Text, Text)]
commands = [("unicode-math","\\inversewhitecircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INVERSE WHITE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9690', commands :: [(Text, Text)]
commands = [("unicode-math","\\invwhiteupperhalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPPER HALF INVERSE WHITE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9691', commands :: [(Text, Text)]
commands = [("unicode-math","\\invwhitelowerhalfcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER HALF INVERSE WHITE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9692', commands :: [(Text, Text)]
commands = [("unicode-math","\\ularc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPPER LEFT QUADRANT CIRCULAR ARC"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9693', commands :: [(Text, Text)]
commands = [("unicode-math","\\urarc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPPER RIGHT QUADRANT CIRCULAR ARC"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9694', commands :: [(Text, Text)]
commands = [("unicode-math","\\lrarc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER RIGHT QUADRANT CIRCULAR ARC"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9695', commands :: [(Text, Text)]
commands = [("unicode-math","\\llarc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER LEFT QUADRANT CIRCULAR ARC"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9696', commands :: [(Text, Text)]
commands = [("unicode-math","\\topsemicircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPPER HALF CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9697', commands :: [(Text, Text)]
commands = [("unicode-math","\\botsemicircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER HALF CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9698', commands :: [(Text, Text)]
commands = [("unicode-math","\\lrblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "lower right triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9699', commands :: [(Text, Text)]
commands = [("unicode-math","\\llblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "lower left triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9700', commands :: [(Text, Text)]
commands = [("unicode-math","\\ulblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "upper left triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9701', commands :: [(Text, Text)]
commands = [("unicode-math","\\urblacktriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "upper right triangle, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9702', commands :: [(Text, Text)]
commands = [("unicode-math","\\smwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE BULLET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9703', commands :: [(Text, Text)]
commands = [("unicode-math","\\squareleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, filled left half"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9704', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarerightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, filled right half"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9705', commands :: [(Text, Text)]
commands = [("unicode-math","\\squareulblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, filled top left corner"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9706', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarelrblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "square, filled bottom right corner"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9707', commands :: [(Text, Text)]
commands = [("stmaryrd","\\boxbar"),("txfonts","\\boxbar"),("unicode-math","\\boxbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "vertical bar in box"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9708', commands :: [(Text, Text)]
commands = [("unicode-math","\\trianglecdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "triangle with centered dot"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9709', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangleleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UP-POINTING TRIANGLE WITH LEFT HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9710', commands :: [(Text, Text)]
commands = [("unicode-math","\\trianglerightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UP-POINTING TRIANGLE WITH RIGHT HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9711', commands :: [(Text, Text)]
commands = [("unicode-math","\\lgwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LARGE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9712', commands :: [(Text, Text)]
commands = [("unicode-math","\\squareulquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SQUARE WITH UPPER LEFT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9713', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarellquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SQUARE WITH LOWER LEFT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9714', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarelrquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SQUARE WITH LOWER RIGHT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9715', commands :: [(Text, Text)]
commands = [("unicode-math","\\squareurquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SQUARE WITH UPPER RIGHT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9716', commands :: [(Text, Text)]
commands = [("unicode-math","\\circleulquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE CIRCLE WITH UPPER LEFT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9717', commands :: [(Text, Text)]
commands = [("unicode-math","\\circlellquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE CIRCLE WITH LOWER LEFT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9718', commands :: [(Text, Text)]
commands = [("unicode-math","\\circlelrquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE CIRCLE WITH LOWER RIGHT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9719', commands :: [(Text, Text)]
commands = [("unicode-math","\\circleurquad")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE CIRCLE WITH UPPER RIGHT QUADRANT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9720', commands :: [(Text, Text)]
commands = [("unicode-math","\\ultriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPPER LEFT TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9721', commands :: [(Text, Text)]
commands = [("unicode-math","\\urtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPPER RIGHT TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9722', commands :: [(Text, Text)]
commands = [("unicode-math","\\lltriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER LEFT TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9723', commands :: [(Text, Text)]
commands = [("amssymb","\\square"),("unicode-math","\\mdwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE MEDIUM SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9724', commands :: [(Text, Text)]
commands = [("amssymb","\\blacksquare"),("unicode-math","\\mdblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK MEDIUM SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9725', commands :: [(Text, Text)]
commands = [("unicode-math","\\mdsmwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE MEDIUM SMALL SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9726', commands :: [(Text, Text)]
commands = [("unicode-math","\\mdsmblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK MEDIUM SMALL SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9727', commands :: [(Text, Text)]
commands = [("unicode-math","\\lrtriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER RIGHT TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9733', commands :: [(Text, Text)]
commands = [("amssymb","\\bigstar"),("unicode-math","\\bigstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "star, filled"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9734', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigwhitestar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "star, open"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9737', commands :: [(Text, Text)]
commands = [("mathabx","\\Sun"),("unicode-math","\\astrosun")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SUN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9740', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "text \\CONJUNCTION (wasysym), CONJUNCTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9744', commands :: [(Text, Text)]
commands = [("wasysym","\\Square")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BALLOT BOX"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9745', commands :: [(Text, Text)]
commands = [("wasysym","\\CheckedBox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "t \\Checkedbox (marvosym), BALLOT BOX WITH CHECK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9746', commands :: [(Text, Text)]
commands = [("wasysym","\\XBox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "t \\Crossedbox (marvosym), BALLOT BOX WITH X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9749', commands :: [(Text, Text)]
commands = [("arevmath","\\steaming")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HOT BEVERAGE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9758', commands :: [(Text, Text)]
commands = [("arevmath","\\pointright")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE RIGHT POINTING INDEX"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9760', commands :: [(Text, Text)]
commands = [("arevmath","\\skull")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SKULL AND CROSSBONES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9761', commands :: [(Text, Text)]
commands = [("unicode-math","\\danger")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CAUTION SIGN, dangerous bend"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9762', commands :: [(Text, Text)]
commands = [("arevmath","\\radiation")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RADIOACTIVE SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9763', commands :: [(Text, Text)]
commands = [("arevmath","\\biohazard")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BIOHAZARD SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9775', commands :: [(Text, Text)]
commands = [("arevmath","\\yinyang")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "YIN YANG"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9785', commands :: [(Text, Text)]
commands = [("wasysym","\\frownie"),("arevmath","\\sadface")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE FROWNING FACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9786', commands :: [(Text, Text)]
commands = [("wasysym","\\smiley"),("arevmath","\\smileface")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SMILING FACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9787', commands :: [(Text, Text)]
commands = [("wasysym","\\blacksmiley"),("arevmath","\\invsmileface"),("unicode-math","\\blacksmiley")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK SMILING FACE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9788', commands :: [(Text, Text)]
commands = [("wasysym","\\sun"),("unicode-math","\\sun")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SUN WITH RAYS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9789', commands :: [(Text, Text)]
commands = [("wasysym","\\rightmoon"),("mathabx","\\rightmoon"),("unicode-math","\\rightmoon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FIRST QUARTER MOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9790', commands :: [(Text, Text)]
commands = [("wasysym","\\leftmoon"),("mathabx","\\leftmoon"),("unicode-math","\\leftmoon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LAST QUARTER MOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9791', commands :: [(Text, Text)]
commands = [("wasysym","\\mercury"),("mathabx","\\Mercury")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MERCURY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9792', commands :: [(Text, Text)]
commands = [("wasysym","\\female"),("mathabx","\\Venus"),("unicode-math","\\female")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "= \\girl (mathabx), venus, female"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9793', commands :: [(Text, Text)]
commands = [("wasysym","\\earth"),("mathabx","\\varEarth")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EARTH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9794', commands :: [(Text, Text)]
commands = [("wasysym","\\male"),("mathabx","\\Mars"),("unicode-math","\\male")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "= \\boy (mathabx), mars, male"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9795', commands :: [(Text, Text)]
commands = [("wasysym","\\jupiter"),("mathabx","\\Jupiter")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "JUPITER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9796', commands :: [(Text, Text)]
commands = [("wasysym","\\saturn"),("mathabx","\\Saturn")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SATURN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9797', commands :: [(Text, Text)]
commands = [("wasysym","\\uranus"),("mathabx","\\Uranus")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "URANUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9798', commands :: [(Text, Text)]
commands = [("wasysym","\\neptune"),("mathabx","\\Neptune")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NEPTUNE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9799', commands :: [(Text, Text)]
commands = [("wasysym","\\pluto"),("mathabx","\\Pluto")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PLUTO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9800', commands :: [(Text, Text)]
commands = [("wasysym","\\aries"),("mathabx","\\Aries")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ARIES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9801', commands :: [(Text, Text)]
commands = [("wasysym","\\taurus"),("mathabx","\\Taurus")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TAURUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9802', commands :: [(Text, Text)]
commands = [("wasysym","\\gemini"),("mathabx","\\Gemini")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "GEMINI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9803', commands :: [(Text, Text)]
commands = [("wasysym","\\cancer")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CANCER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9804', commands :: [(Text, Text)]
commands = [("wasysym","\\leo"),("mathabx","\\Leo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9805', commands :: [(Text, Text)]
commands = [("wasysym","\\virgo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "VIRGO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9806', commands :: [(Text, Text)]
commands = [("wasysym","\\libra"),("mathabx","\\Libra")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LIBRA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9807', commands :: [(Text, Text)]
commands = [("wasysym","\\scorpio"),("mathabx","\\Scorpio")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SCORPIUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9808', commands :: [(Text, Text)]
commands = [("wasysym","\\sagittarius")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SAGITTARIUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9809', commands :: [(Text, Text)]
commands = [("wasysym","\\capricornus")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CAPRICORN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9810', commands :: [(Text, Text)]
commands = [("wasysym","\\aquarius")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "AQUARIUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9811', commands :: [(Text, Text)]
commands = [("wasysym","\\pisces")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PISCES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9824', commands :: [(Text, Text)]
commands = [("base","\\spadesuit"),("unicode-math","\\spadesuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "spades suit symbol"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9825', commands :: [(Text, Text)]
commands = [("base","\\heartsuit"),("unicode-math","\\heartsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "heart suit symbol"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9826', commands :: [(Text, Text)]
commands = [("base","\\diamondsuit"),("unicode-math","\\diamondsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "diamond suit symbol"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9827', commands :: [(Text, Text)]
commands = [("base","\\clubsuit"),("unicode-math","\\clubsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "club suit symbol"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9828', commands :: [(Text, Text)]
commands = [("txfonts","\\varspadesuit"),("arevmath","\\varspade"),("unicode-math","\\varspadesuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "spade, white (card suit)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9829', commands :: [(Text, Text)]
commands = [("txfonts","\\varheartsuit"),("arevmath","\\varheart"),("unicode-math","\\varheartsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "filled heart (card suit)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9830', commands :: [(Text, Text)]
commands = [("txfonts","\\vardiamondsuit"),("arevmath","\\vardiamond"),("unicode-math","\\vardiamondsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "filled diamond (card suit)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9831', commands :: [(Text, Text)]
commands = [("txfonts","\\varclubsuit"),("arevmath","\\varclub"),("unicode-math","\\varclubsuit")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "club, white (card suit)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9833', commands :: [(Text, Text)]
commands = [("arevmath","\\quarternote"),("wasysym","\\quarternote"),("unicode-math","\\quarternote")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "music note (sung text sign)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9834', commands :: [(Text, Text)]
commands = [("arevmath","\\eighthnote"),("unicode-math","\\eighthnote")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EIGHTH NOTE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9835', commands :: [(Text, Text)]
commands = [("wasysym","\\twonotes"),("unicode-math","\\twonotes")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BEAMED EIGHTH NOTES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9836', commands :: [(Text, Text)]
commands = [("arevmath","\\sixteenthnote")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BEAMED SIXTEENTH NOTES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9837', commands :: [(Text, Text)]
commands = [("base","\\flat"),("unicode-math","\\flat")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "musical flat"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9838', commands :: [(Text, Text)]
commands = [("base","\\natural"),("unicode-math","\\natural")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "music natural"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9839', commands :: [(Text, Text)]
commands = [("base","\\sharp"),("oz","\\#"),("unicode-math","\\sharp")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MUSIC SHARP SIGN, z notation infix bag count"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9851', commands :: [(Text, Text)]
commands = [("arevmath","\\recycle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK UNIVERSAL RECYCLING SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9854', commands :: [(Text, Text)]
commands = [("unicode-math","\\acidfree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PERMANENT PAPER SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9856', commands :: [(Text, Text)]
commands = [("unicode-math","\\dicei")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIE FACE-1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9857', commands :: [(Text, Text)]
commands = [("unicode-math","\\diceii")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIE FACE-2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9858', commands :: [(Text, Text)]
commands = [("unicode-math","\\diceiii")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIE FACE-3"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9859', commands :: [(Text, Text)]
commands = [("unicode-math","\\diceiv")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIE FACE-4"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9860', commands :: [(Text, Text)]
commands = [("unicode-math","\\dicev")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIE FACE-5"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9861', commands :: [(Text, Text)]
commands = [("unicode-math","\\dicevi")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIE FACE-6"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9862', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledrightdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE CIRCLE WITH DOT RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9863', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledtwodots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE CIRCLE WITH TWO DOTS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9864', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackcircledrightdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK CIRCLE WITH WHITE DOT RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9865', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackcircledtwodots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK CIRCLE WITH TWO WHITE DOTS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9875', commands :: [(Text, Text)]
commands = [("arevmath","\\anchor")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ANCHOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9876', commands :: [(Text, Text)]
commands = [("arevmath","\\swords")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CROSSED SWORDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9888', commands :: [(Text, Text)]
commands = [("arevmath","\\warning")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WARNING SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9893', commands :: [(Text, Text)]
commands = [("unicode-math","\\Hermaphrodite")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MALE AND FEMALE SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9898', commands :: [(Text, Text)]
commands = [("txfonts","\\medcirc"),("unicode-math","\\mdwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEDIUM WHITE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9899', commands :: [(Text, Text)]
commands = [("txfonts","\\medbullet"),("unicode-math","\\mdblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEDIUM BLACK CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9900', commands :: [(Text, Text)]
commands = [("unicode-math","\\mdsmwhtcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEDIUM SMALL WHITE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9906', commands :: [(Text, Text)]
commands = [("unicode-math","\\neuter")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NEUTER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\9998', commands :: [(Text, Text)]
commands = [("arevmath","\\pencil")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LOWER RIGHT PENCIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10003', commands :: [(Text, Text)]
commands = [("amsfonts","\\checkmark"),("arevmath","\\ballotcheck"),("unicode-math","\\checkmark")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "tick, CHECK MARK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10007', commands :: [(Text, Text)]
commands = [("arevmath","\\ballotx")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BALLOT X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10016', commands :: [(Text, Text)]
commands = [("amsfonts","\\maltese"),("unicode-math","\\maltese")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MALTESE CROSS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10026', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLED WHITE STAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10038', commands :: [(Text, Text)]
commands = [("unicode-math","\\varstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SIX POINTED BLACK STAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10045', commands :: [(Text, Text)]
commands = [("unicode-math","\\dingasterisk")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HEAVY TEARDROP-SPOKED ASTERISK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10098', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LIGHT LEFT TORTOISE SHELL BRACKET ORNAMENT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10099', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "LIGHT RIGHT TORTOISE SHELL BRACKET ORNAMENT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10139', commands :: [(Text, Text)]
commands = [("unicode-math","\\draftingarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "right arrow with bold head (drafting)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10146', commands :: [(Text, Text)]
commands = [("arevmath","\\arrowbullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "THREE-D TOP-LIGHTED RIGHTWARDS ARROWHEAD"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10176', commands :: [(Text, Text)]
commands = [("unicode-math","\\threedangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "THREE DIMENSIONAL ANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10177', commands :: [(Text, Text)]
commands = [("unicode-math","\\whiteinwhitetriangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE TRIANGLE CONTAINING SMALL WHITE TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10178', commands :: [(Text, Text)]
commands = [("base","\\perp"),("unicode-math","\\perp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PERPENDICULAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10179', commands :: [(Text, Text)]
commands = [("unicode-math","\\subsetcirc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "OPEN SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10180', commands :: [(Text, Text)]
commands = [("unicode-math","\\supsetcirc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "OPEN SUPERSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10181', commands :: [(Text, Text)]
commands = [("stmaryrd","\\Lbag"),("txfonts","\\Lbag"),("stmaryrd -oz","\\lbag"),("unicode-math","\\lbag")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT S-SHAPED BAG DELIMITER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10182', commands :: [(Text, Text)]
commands = [("stmaryrd","\\Rbag"),("txfonts","\\Rbag"),("stmaryrd -oz","\\rbag"),("unicode-math","\\rbag")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT S-SHAPED BAG DELIMITER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10183', commands :: [(Text, Text)]
commands = [("unicode-math","\\veedot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "OR WITH DOT INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10184', commands :: [(Text, Text)]
commands = [("unicode-math","\\bsolhsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "REVERSE SOLIDUS PRECEDING SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10185', commands :: [(Text, Text)]
commands = [("unicode-math","\\suphsol")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET PRECEDING SOLIDUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10188', commands :: [(Text, Text)]
commands = [("unicode-math","\\longdivision")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LONG DIVISION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10192', commands :: [(Text, Text)]
commands = [("txfonts","\\Diamonddot"),("unicode-math","\\diamondcdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE DIAMOND WITH CENTRED DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10193', commands :: [(Text, Text)]
commands = [("unicode-math","\\wedgedot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "AND WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10194', commands :: [(Text, Text)]
commands = [("unicode-math","\\upin")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF OPENING UPWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10195', commands :: [(Text, Text)]
commands = [("unicode-math","\\pullback")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LOWER RIGHT CORNER WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10196', commands :: [(Text, Text)]
commands = [("unicode-math","\\pushout")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPPER LEFT CORNER WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10197', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftouterjoin")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LEFT OUTER JOIN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10198', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightouterjoin")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "RIGHT OUTER JOIN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10199', commands :: [(Text, Text)]
commands = [("unicode-math","\\fullouterjoin")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "FULL OUTER JOIN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10200', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigbot")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LARGE UP TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10201', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigtop")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LARGE DOWN TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10202', commands :: [(Text, Text)]
commands = [("unicode-math","\\DashVDash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT AND RIGHT DOUBLE TURNSTILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10203', commands :: [(Text, Text)]
commands = [("unicode-math","\\dashVdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT AND RIGHT TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10204', commands :: [(Text, Text)]
commands = [("txfonts","\\multimapinv"),("unicode-math","\\multimapinv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT MULTIMAP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10205', commands :: [(Text, Text)]
commands = [("unicode-math","\\vlongdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "long left tack"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10206', commands :: [(Text, Text)]
commands = [("unicode-math","\\longdashv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "long right tack"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10207', commands :: [(Text, Text)]
commands = [("unicode-math","\\cirbot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UP TACK WITH CIRCLE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10208', commands :: [(Text, Text)]
commands = [("unicode-math","\\lozengeminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOZENGE DIVIDED BY HORIZONTAL RULE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10209', commands :: [(Text, Text)]
commands = [("unicode-math","\\concavediamond")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE CONCAVE-SIDED DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10210', commands :: [(Text, Text)]
commands = [("unicode-math","\\concavediamondtickleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE CONCAVE-SIDED DIAMOND WITH LEFTWARDS TICK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10211', commands :: [(Text, Text)]
commands = [("unicode-math","\\concavediamondtickright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE CONCAVE-SIDED DIAMOND WITH RIGHTWARDS TICK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10212', commands :: [(Text, Text)]
commands = [("unicode-math","\\whitesquaretickleft")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE SQUARE WITH LEFTWARDS TICK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10213', commands :: [(Text, Text)]
commands = [("unicode-math","\\whitesquaretickright")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE SQUARE WITH RIGHTWARDS TICK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10214', commands :: [(Text, Text)]
commands = [("stmaryrd","\\llbracket"),("wrisym","\\llbracket"),("kpfonts","\\llbracket"),("fourier","\\llbracket"),("mathbbol","\\Lbrack"),("unicode-math","\\lBrack")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "= \\lbag (oz -stmaryrd), MATHEMATICAL LEFT WHITE SQUARE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10215', commands :: [(Text, Text)]
commands = [("stmaryrd","\\rrbracket"),("wrisym","\\rrbracket"),("kpfonts","\\rrbracket"),("fourier","\\rrbracket"),("mathbbol","\\Rbrack"),("unicode-math","\\rBrack")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "= \\rbag (oz -stmaryrd), MATHEMATICAL RIGHT WHITE SQUARE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10216', commands :: [(Text, Text)]
commands = [("base","\\langle"),("unicode-math","\\langle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "MATHEMATICAL LEFT ANGLE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10217', commands :: [(Text, Text)]
commands = [("base","\\rangle"),("unicode-math","\\rangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "MATHEMATICAL RIGHT ANGLE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10218', commands :: [(Text, Text)]
commands = [("oz","\\lang"),("unicode-math","\\lAngle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "MATHEMATICAL LEFT DOUBLE ANGLE BRACKET, z notation left chevron bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10219', commands :: [(Text, Text)]
commands = [("oz","\\rang"),("unicode-math","\\rAngle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "MATHEMATICAL RIGHT DOUBLE ANGLE BRACKET, z notation right chevron bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10220', commands :: [(Text, Text)]
commands = [("unicode-math","\\Lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "MATHEMATICAL LEFT WHITE TORTOISE SHELL BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10221', commands :: [(Text, Text)]
commands = [("unicode-math","\\Rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "MATHEMATICAL RIGHT WHITE TORTOISE SHELL BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10222', commands :: [(Text, Text)]
commands = [("base","\\lgroup")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "MATHEMATICAL LEFT FLATTENED PARENTHESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10223', commands :: [(Text, Text)]
commands = [("base","\\rgroup")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "MATHEMATICAL RIGHT FLATTENED PARENTHESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10224', commands :: [(Text, Text)]
commands = [("unicode-math","\\UUparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS QUADRUPLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10225', commands :: [(Text, Text)]
commands = [("unicode-math","\\DDownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS QUADRUPLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10226', commands :: [(Text, Text)]
commands = [("unicode-math","\\acwgapcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ANTICLOCKWISE GAPPED CIRCLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10227', commands :: [(Text, Text)]
commands = [("unicode-math","\\cwgapcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CLOCKWISE GAPPED CIRCLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10228', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowonoplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHT ARROW WITH CIRCLED PLUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10229', commands :: [(Text, Text)]
commands = [("base","\\longleftarrow"),("unicode-math","\\longleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10230', commands :: [(Text, Text)]
commands = [("base","\\longrightarrow"),("unicode-math","\\longrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10231', commands :: [(Text, Text)]
commands = [("base","\\longleftrightarrow"),("unicode-math","\\longleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG LEFT RIGHT ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10232', commands :: [(Text, Text)]
commands = [("base","\\Longleftarrow"),("amsmath","\\impliedby"),("unicode-math","\\Longleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG LEFTWARDS DOUBLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10233', commands :: [(Text, Text)]
commands = [("base","\\Longrightarrow"),("amsmath","\\implies"),("unicode-math","\\Longrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG RIGHTWARDS DOUBLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10234', commands :: [(Text, Text)]
commands = [("base","\\Longleftrightarrow"),("oz","\\iff"),("unicode-math","\\Longleftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG LEFT RIGHT DOUBLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10235', commands :: [(Text, Text)]
commands = [("stmaryrd","\\longmapsfrom"),("kpfonts","\\longmappedfrom"),("unicode-math","\\longmapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG LEFTWARDS ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10236', commands :: [(Text, Text)]
commands = [("base","\\longmapsto"),("unicode-math","\\longmapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG RIGHTWARDS ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10237', commands :: [(Text, Text)]
commands = [("stmaryrd","\\Longmapsfrom"),("kpfonts","\\Longmappedfrom"),("unicode-math","\\Longmapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG LEFTWARDS DOUBLE ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10238', commands :: [(Text, Text)]
commands = [("stmaryrd","\\Longmapsto"),("unicode-math","\\Longmapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG RIGHTWARDS DOUBLE ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10239', commands :: [(Text, Text)]
commands = [("unicode-math","\\longrightsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG RIGHTWARDS SQUIGGLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10496', commands :: [(Text, Text)]
commands = [("oz","\\psur"),("oz","\\psurj"),("unicode-math","\\nvtwoheadrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TWO-HEADED ARROW WITH VERTICAL STROKE, z notation partial surjection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10497', commands :: [(Text, Text)]
commands = [("unicode-math","\\nVtwoheadrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TWO-HEADED ARROW WITH DOUBLE VERTICAL STROKE, z notation finite surjection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10498', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvLeftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS DOUBLE ARROW WITH VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10499', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvRightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS DOUBLE ARROW WITH VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10500', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvLeftrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT RIGHT DOUBLE ARROW WITH VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10501', commands :: [(Text, Text)]
commands = [("unicode-math","\\twoheadmapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TWO-HEADED ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10502', commands :: [(Text, Text)]
commands = [("stmaryrd","\\Mapsfrom"),("kpfonts","\\Mappedfrom"),("unicode-math","\\Mapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS DOUBLE ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10503', commands :: [(Text, Text)]
commands = [("stmaryrd","\\Mapsto"),("unicode-math","\\Mapsto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS DOUBLE ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10504', commands :: [(Text, Text)]
commands = [("unicode-math","\\downarrowbarred")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS ARROW WITH HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10505', commands :: [(Text, Text)]
commands = [("unicode-math","\\uparrowbarred")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS ARROW WITH HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10506', commands :: [(Text, Text)]
commands = [("unicode-math","\\Uuparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS TRIPLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10507', commands :: [(Text, Text)]
commands = [("unicode-math","\\Ddownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS TRIPLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10508', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS DOUBLE DASH ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10509', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS DOUBLE DASH ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10510', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftdbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS TRIPLE DASH ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10511', commands :: [(Text, Text)]
commands = [("unicode-math","\\dbkarow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TRIPLE DASH ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10512', commands :: [(Text, Text)]
commands = [("unicode-math","\\drbkarow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TWO-HEADED TRIPLE DASH ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10513', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightdotarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW WITH DOTTED STEM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10514', commands :: [(Text, Text)]
commands = [("wrisym","\\UpArrowBar"),("unicode-math","\\baruparrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS ARROW TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10515', commands :: [(Text, Text)]
commands = [("wrisym","\\DownArrowBar"),("unicode-math","\\downarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS ARROW TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10516', commands :: [(Text, Text)]
commands = [("oz","\\pinj"),("unicode-math","\\nvrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW WITH TAIL WITH VERTICAL STROKE, z notation partial injection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10517', commands :: [(Text, Text)]
commands = [("oz","\\finj"),("unicode-math","\\nVrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE, z notation finite injection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10518', commands :: [(Text, Text)]
commands = [("oz","\\bij"),("unicode-math","\\twoheadrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TWO-HEADED ARROW WITH TAIL, z notation bijection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10519', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvtwoheadrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TWO-HEADED ARROW WITH TAIL WITH VERTICAL STROKE, z notation surjective injection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10520', commands :: [(Text, Text)]
commands = [("unicode-math","\\nVtwoheadrightarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS TWO-HEADED ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE, z notation finite surjective injection"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10521', commands :: [(Text, Text)]
commands = [("unicode-math","\\lefttail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW-TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10522', commands :: [(Text, Text)]
commands = [("unicode-math","\\righttail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW-TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10523', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftdbltail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS DOUBLE ARROW-TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10524', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightdbltail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS DOUBLE ARROW-TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10525', commands :: [(Text, Text)]
commands = [("unicode-math","\\diamondleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW TO BLACK DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10526', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW TO BLACK DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10527', commands :: [(Text, Text)]
commands = [("unicode-math","\\diamondleftarrowbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW FROM BAR TO BLACK DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10528', commands :: [(Text, Text)]
commands = [("unicode-math","\\barrightarrowdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW FROM BAR TO BLACK DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10529', commands :: [(Text, Text)]
commands = [("unicode-math","\\nwsearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NORTH WEST AND SOUTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10530', commands :: [(Text, Text)]
commands = [("unicode-math","\\neswarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NORTH EAST AND SOUTH WEST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10531', commands :: [(Text, Text)]
commands = [("unicode-math","\\hknwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NORTH WEST ARROW WITH HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10532', commands :: [(Text, Text)]
commands = [("unicode-math","\\hknearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NORTH EAST ARROW WITH HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10533', commands :: [(Text, Text)]
commands = [("unicode-math","\\hksearow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SOUTH EAST ARROW WITH HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10534', commands :: [(Text, Text)]
commands = [("unicode-math","\\hkswarow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SOUTH WEST ARROW WITH HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10535', commands :: [(Text, Text)]
commands = [("unicode-math","\\tona")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NORTH WEST ARROW AND NORTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10536', commands :: [(Text, Text)]
commands = [("unicode-math","\\toea")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NORTH EAST ARROW AND SOUTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10537', commands :: [(Text, Text)]
commands = [("unicode-math","\\tosa")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SOUTH EAST ARROW AND SOUTH WEST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10538', commands :: [(Text, Text)]
commands = [("unicode-math","\\towa")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SOUTH WEST ARROW AND NORTH WEST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10539', commands :: [(Text, Text)]
commands = [("unicode-math","\\rdiagovfdiag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RISING DIAGONAL CROSSING FALLING DIAGONAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10540', commands :: [(Text, Text)]
commands = [("unicode-math","\\fdiagovrdiag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FALLING DIAGONAL CROSSING RISING DIAGONAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10541', commands :: [(Text, Text)]
commands = [("unicode-math","\\seovnearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SOUTH EAST ARROW CROSSING NORTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10542', commands :: [(Text, Text)]
commands = [("unicode-math","\\neovsearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH EAST ARROW CROSSING SOUTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10543', commands :: [(Text, Text)]
commands = [("unicode-math","\\fdiagovnearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FALLING DIAGONAL CROSSING NORTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10544', commands :: [(Text, Text)]
commands = [("unicode-math","\\rdiagovsearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RISING DIAGONAL CROSSING SOUTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10545', commands :: [(Text, Text)]
commands = [("unicode-math","\\neovnwarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH EAST ARROW CROSSING NORTH WEST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10546', commands :: [(Text, Text)]
commands = [("unicode-math","\\nwovnearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH WEST ARROW CROSSING NORTH EAST ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10547', commands :: [(Text, Text)]
commands = [("txfonts","\\leadsto"),("unicode-math","\\rightcurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "WAVE ARROW POINTING DIRECTLY RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10548', commands :: [(Text, Text)]
commands = [("unicode-math","\\uprightcurvearrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ARROW POINTING RIGHTWARDS THEN CURVING UPWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10549', commands :: [(Text, Text)]
commands = [("unicode-math","\\downrightcurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ARROW POINTING RIGHTWARDS THEN CURVING DOWNWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10550', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftdowncurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ARROW POINTING DOWNWARDS THEN CURVING LEFTWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10551', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightdowncurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ARROW POINTING DOWNWARDS THEN CURVING RIGHTWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10552', commands :: [(Text, Text)]
commands = [("unicode-math","\\cwrightarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHT-SIDE ARC CLOCKWISE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10553', commands :: [(Text, Text)]
commands = [("unicode-math","\\acwleftarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT-SIDE ARC ANTICLOCKWISE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10554', commands :: [(Text, Text)]
commands = [("unicode-math","\\acwoverarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TOP ARC ANTICLOCKWISE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10555', commands :: [(Text, Text)]
commands = [("unicode-math","\\acwunderarcarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "BOTTOM ARC ANTICLOCKWISE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10556', commands :: [(Text, Text)]
commands = [("unicode-math","\\curvearrowrightminus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TOP ARC CLOCKWISE ARROW WITH MINUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10557', commands :: [(Text, Text)]
commands = [("unicode-math","\\curvearrowleftplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TOP ARC ANTICLOCKWISE ARROW WITH PLUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10558', commands :: [(Text, Text)]
commands = [("unicode-math","\\cwundercurvearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LOWER RIGHT SEMICIRCULAR CLOCKWISE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10559', commands :: [(Text, Text)]
commands = [("unicode-math","\\ccwundercurvearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LOWER LEFT SEMICIRCULAR ANTICLOCKWISE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10560', commands :: [(Text, Text)]
commands = [("unicode-math","\\acwcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ANTICLOCKWISE CLOSED CIRCLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10561', commands :: [(Text, Text)]
commands = [("unicode-math","\\cwcirclearrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CLOCKWISE CLOSED CIRCLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10562', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowshortleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW ABOVE SHORT LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10563', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowshortrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW ABOVE SHORT RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10564', commands :: [(Text, Text)]
commands = [("unicode-math","\\shortrightarrowleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SHORT RIGHTWARDS ARROW ABOVE LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10565', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW WITH PLUS BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10566', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW WITH PLUS BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10567', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowx")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW THROUGH X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10568', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftrightarrowcircle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT RIGHT ARROW THROUGH SMALL CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10569', commands :: [(Text, Text)]
commands = [("unicode-math","\\twoheaduparrowcircle")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS TWO-HEADED ARROW FROM SMALL CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10570', commands :: [(Text, Text)]
commands = [("mathabx","\\leftrightharpoon"),("unicode-math","\\leftrightharpoonupdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT BARB UP RIGHT BARB DOWN HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10571', commands :: [(Text, Text)]
commands = [("mathabx","\\rightleftharpoon"),("unicode-math","\\leftrightharpoondownup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT BARB DOWN RIGHT BARB UP HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10572', commands :: [(Text, Text)]
commands = [("unicode-math","\\updownharpoonrightleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UP BARB RIGHT DOWN BARB LEFT HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10573', commands :: [(Text, Text)]
commands = [("unicode-math","\\updownharpoonleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UP BARB LEFT DOWN BARB RIGHT HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10574', commands :: [(Text, Text)]
commands = [("wrisym","\\leftrightharpoonup"),("unicode-math","\\leftrightharpoonupup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT BARB UP RIGHT BARB UP HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10575', commands :: [(Text, Text)]
commands = [("wrisym","\\rightupdownharpoon"),("unicode-math","\\updownharpoonrightright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UP BARB RIGHT DOWN BARB RIGHT HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10576', commands :: [(Text, Text)]
commands = [("wrisym","\\leftrightharpoondown"),("unicode-math","\\leftrightharpoondowndown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT BARB DOWN RIGHT BARB DOWN HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10577', commands :: [(Text, Text)]
commands = [("wrisym","\\leftupdownharpoon"),("unicode-math","\\updownharpoonleftleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UP BARB LEFT DOWN BARB LEFT HARPOON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10578', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftVectorBar"),("unicode-math","\\barleftharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB UP TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10579', commands :: [(Text, Text)]
commands = [("wrisym","\\RightVectorBar"),("unicode-math","\\rightharpoonupbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB UP TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10580', commands :: [(Text, Text)]
commands = [("wrisym","\\RightUpVectorBar"),("unicode-math","\\barupharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS HARPOON WITH BARB RIGHT TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10581', commands :: [(Text, Text)]
commands = [("wrisym","\\RightDownVectorBar"),("unicode-math","\\downharpoonrightbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS HARPOON WITH BARB RIGHT TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10582', commands :: [(Text, Text)]
commands = [("wrisym","\\DownLeftVectorBar"),("unicode-math","\\barleftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB DOWN TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10583', commands :: [(Text, Text)]
commands = [("wrisym","\\DownRightVectorBar"),("unicode-math","\\rightharpoondownbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB DOWN TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10584', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftUpVectorBar"),("unicode-math","\\barupharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS HARPOON WITH BARB LEFT TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10585', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftDownVectorBar"),("unicode-math","\\downharpoonleftbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS HARPOON WITH BARB LEFT TO BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10586', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftTeeVector"),("unicode-math","\\leftharpoonupbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB UP FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10587', commands :: [(Text, Text)]
commands = [("wrisym","\\RightTeeVector"),("unicode-math","\\barrightharpoonup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB UP FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10588', commands :: [(Text, Text)]
commands = [("wrisym","\\RightUpTeeVector"),("unicode-math","\\upharpoonrightbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS HARPOON WITH BARB RIGHT FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10589', commands :: [(Text, Text)]
commands = [("wrisym","\\RightDownTeeVector"),("unicode-math","\\bardownharpoonright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS HARPOON WITH BARB RIGHT FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10590', commands :: [(Text, Text)]
commands = [("wrisym","\\DownLeftTeeVector"),("unicode-math","\\leftharpoondownbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB DOWN FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10591', commands :: [(Text, Text)]
commands = [("wrisym","\\DownRightTeeVector"),("unicode-math","\\barrightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB DOWN FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10592', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftUpTeeVector"),("unicode-math","\\upharpoonleftbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS HARPOON WITH BARB LEFT FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10593', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftDownTeeVector"),("unicode-math","\\bardownharpoonleft")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS HARPOON WITH BARB LEFT FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10594', commands :: [(Text, Text)]
commands = [("mathabx","\\leftleftharpoons"),("unicode-math","\\leftharpoonsupdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB UP ABOVE LEFTWARDS HARPOON WITH BARB DOWN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10595', commands :: [(Text, Text)]
commands = [("mathabx","\\upupharpoons"),("unicode-math","\\upharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS HARPOON WITH BARB LEFT BESIDE UPWARDS HARPOON WITH BARB RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10596', commands :: [(Text, Text)]
commands = [("mathabx","\\rightrightharpoons"),("unicode-math","\\rightharpoonsupdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB UP ABOVE RIGHTWARDS HARPOON WITH BARB DOWN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10597', commands :: [(Text, Text)]
commands = [("mathabx","\\downdownharpoons"),("unicode-math","\\downharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS HARPOON WITH BARB LEFT BESIDE DOWNWARDS HARPOON WITH BARB RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10598', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftrightharpoonsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB UP ABOVE RIGHTWARDS HARPOON WITH BARB UP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10599', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftrightharpoonsdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB DOWN ABOVE RIGHTWARDS HARPOON WITH BARB DOWN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10600', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightleftharpoonsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB UP ABOVE LEFTWARDS HARPOON WITH BARB UP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10601', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightleftharpoonsdown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB DOWN ABOVE LEFTWARDS HARPOON WITH BARB DOWN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10602', commands :: [(Text, Text)]
commands = [("mathabx","\\leftbarharpoon"),("unicode-math","\\leftharpoonupdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB UP ABOVE LONG DASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10603', commands :: [(Text, Text)]
commands = [("mathabx","\\barleftharpoon"),("unicode-math","\\dashleftharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS HARPOON WITH BARB DOWN BELOW LONG DASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10604', commands :: [(Text, Text)]
commands = [("mathabx","\\rightbarharpoon"),("unicode-math","\\rightharpoonupdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB UP ABOVE LONG DASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10605', commands :: [(Text, Text)]
commands = [("mathabx","\\barrightharpoon"),("unicode-math","\\dashrightharpoondown")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS HARPOON WITH BARB DOWN BELOW LONG DASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10606', commands :: [(Text, Text)]
commands = [("mathabx","\\updownharpoons"),("wrisym","\\upequilibrium"),("unicode-math","\\updownharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UPWARDS HARPOON WITH BARB LEFT BESIDE DOWNWARDS HARPOON WITH BARB RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10607', commands :: [(Text, Text)]
commands = [("mathabx","\\downupharpoons"),("wrisym","\\uprevequilibrium"),("unicode-math","\\downupharpoonsleftright")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWNWARDS HARPOON WITH BARB LEFT BESIDE UPWARDS HARPOON WITH BARB RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10608', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightimply")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHT DOUBLE ARROW WITH ROUNDED HEAD"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10609', commands :: [(Text, Text)]
commands = [("unicode-math","\\equalrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN ABOVE RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10610', commands :: [(Text, Text)]
commands = [("unicode-math","\\similarrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TILDE OPERATOR ABOVE RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10611', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW ABOVE TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10612', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW ABOVE TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10613', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW ABOVE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10614', commands :: [(Text, Text)]
commands = [("unicode-math","\\ltlarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN ABOVE LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10615', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW THROUGH LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10616', commands :: [(Text, Text)]
commands = [("unicode-math","\\gtrarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN ABOVE RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10617', commands :: [(Text, Text)]
commands = [("unicode-math","\\subrarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET ABOVE RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10618', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowsubset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW THROUGH SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10619', commands :: [(Text, Text)]
commands = [("unicode-math","\\suplarr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET ABOVE LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10620', commands :: [(Text, Text)]
commands = [("txfonts","\\strictfi"),("unicode-math","\\leftfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT FISH TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10621', commands :: [(Text, Text)]
commands = [("txfonts","\\strictif"),("unicode-math","\\rightfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHT FISH TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10622', commands :: [(Text, Text)]
commands = [("unicode-math","\\upfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "UP FISH TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10623', commands :: [(Text, Text)]
commands = [("unicode-math","\\downfishtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOWN FISH TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10624', commands :: [(Text, Text)]
commands = [("fourier","\\VERT"),("unicode-math","\\Vvert")], category :: TeXSymbolType
category = TeXSymbolType
Fence, comments :: Text
comments = "TRIPLE VERTICAL BAR DELIMITER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10625', commands :: [(Text, Text)]
commands = [("oz","\\spot"),("oz","\\dot"),("unicode-math","\\mdsmblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "Z NOTATION SPOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10626', commands :: [(Text, Text)]
commands = [("unicode-math","\\typecolon")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "Z NOTATION TYPE COLON, (present in bbold font but no command)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10627', commands :: [(Text, Text)]
commands = [("unicode-math","\\lBrace")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT WHITE CURLY BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10628', commands :: [(Text, Text)]
commands = [("unicode-math","\\rBrace")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT WHITE CURLY BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10629', commands :: [(Text, Text)]
commands = [("mathbbol","\\Lparen"),("unicode-math","\\lParen")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT WHITE PARENTHESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10630', commands :: [(Text, Text)]
commands = [("mathbbol","\\Rparen"),("unicode-math","\\rParen")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT WHITE PARENTHESIS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10631', commands :: [(Text, Text)]
commands = [("oz","\\limg"),("stmaryrd","\\llparenthesis"),("unicode-math","\\llparenthesis")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "Z NOTATION LEFT IMAGE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10632', commands :: [(Text, Text)]
commands = [("oz","\\rimg"),("stmaryrd","\\rrparenthesis"),("unicode-math","\\rrparenthesis")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "Z NOTATION RIGHT IMAGE BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10633', commands :: [(Text, Text)]
commands = [("oz","\\lblot"),("unicode-math","\\llangle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "Z NOTATION LEFT BINDING BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10634', commands :: [(Text, Text)]
commands = [("oz","\\rblot"),("unicode-math","\\rrangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "Z NOTATION RIGHT BINDING BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10635', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbrackubar")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT SQUARE BRACKET WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10636', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbrackubar")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT SQUARE BRACKET WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10637', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbrackultick")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT SQUARE BRACKET WITH TICK IN TOP CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10638', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbracklrtick")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT SQUARE BRACKET WITH TICK IN BOTTOM CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10639', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbracklltick")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT SQUARE BRACKET WITH TICK IN BOTTOM CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10640', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbrackurtick")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT SQUARE BRACKET WITH TICK IN TOP CORNER"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10641', commands :: [(Text, Text)]
commands = [("unicode-math","\\langledot")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT ANGLE BRACKET WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10642', commands :: [(Text, Text)]
commands = [("unicode-math","\\rangledot")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT ANGLE BRACKET WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10643', commands :: [(Text, Text)]
commands = [("unicode-math","\\lparenless")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT ARC LESS-THAN BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10644', commands :: [(Text, Text)]
commands = [("unicode-math","\\rparengtr")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT ARC GREATER-THAN BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10645', commands :: [(Text, Text)]
commands = [("unicode-math","\\Lparengtr")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "DOUBLE LEFT ARC GREATER-THAN BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10646', commands :: [(Text, Text)]
commands = [("unicode-math","\\Rparenless")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "DOUBLE RIGHT ARC LESS-THAN BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10647', commands :: [(Text, Text)]
commands = [("unicode-math","\\lblkbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT BLACK TORTOISE SHELL BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10648', commands :: [(Text, Text)]
commands = [("unicode-math","\\rblkbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT BLACK TORTOISE SHELL BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10649', commands :: [(Text, Text)]
commands = [("unicode-math","\\fourvdots")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOTTED FENCE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10650', commands :: [(Text, Text)]
commands = [("unicode-math","\\vzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "VERTICAL ZIGZAG LINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10651', commands :: [(Text, Text)]
commands = [("unicode-math","\\measuredangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE OPENING LEFT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10652', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightanglesqr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHT ANGLE VARIANT WITH SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10653', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightanglemdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED RIGHT ANGLE WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10654', commands :: [(Text, Text)]
commands = [("unicode-math","\\angles")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ANGLE WITH S INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10655', commands :: [(Text, Text)]
commands = [("unicode-math","\\angdnr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ACUTE ANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10656', commands :: [(Text, Text)]
commands = [("unicode-math","\\gtlpar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SPHERICAL ANGLE OPENING LEFT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10657', commands :: [(Text, Text)]
commands = [("unicode-math","\\sphericalangleup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SPHERICAL ANGLE OPENING UP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10658', commands :: [(Text, Text)]
commands = [("unicode-math","\\turnangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TURNED ANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10659', commands :: [(Text, Text)]
commands = [("unicode-math","\\revangle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "REVERSED ANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10660', commands :: [(Text, Text)]
commands = [("unicode-math","\\angleubar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ANGLE WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10661', commands :: [(Text, Text)]
commands = [("unicode-math","\\revangleubar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "REVERSED ANGLE WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10662', commands :: [(Text, Text)]
commands = [("unicode-math","\\wideangledown")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "OBLIQUE ANGLE OPENING UP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10663', commands :: [(Text, Text)]
commands = [("unicode-math","\\wideangleup")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "OBLIQUE ANGLE OPENING DOWN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10664', commands :: [(Text, Text)]
commands = [("unicode-math","\\measanglerutone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING UP AND RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10665', commands :: [(Text, Text)]
commands = [("unicode-math","\\measanglelutonw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING UP AND LEFT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10666', commands :: [(Text, Text)]
commands = [("unicode-math","\\measanglerdtose")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING DOWN AND RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10667', commands :: [(Text, Text)]
commands = [("unicode-math","\\measangleldtosw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING DOWN AND LEFT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10668', commands :: [(Text, Text)]
commands = [("unicode-math","\\measangleurtone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING RIGHT AND UP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10669', commands :: [(Text, Text)]
commands = [("unicode-math","\\measangleultonw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING LEFT AND UP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10670', commands :: [(Text, Text)]
commands = [("unicode-math","\\measangledrtose")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING RIGHT AND DOWN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10671', commands :: [(Text, Text)]
commands = [("unicode-math","\\measangledltosw")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING LEFT AND DOWN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10672', commands :: [(Text, Text)]
commands = [("unicode-math","\\revemptyset")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "REVERSED EMPTY SET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10673', commands :: [(Text, Text)]
commands = [("unicode-math","\\emptysetobar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EMPTY SET WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10674', commands :: [(Text, Text)]
commands = [("unicode-math","\\emptysetocirc")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EMPTY SET WITH SMALL CIRCLE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10675', commands :: [(Text, Text)]
commands = [("unicode-math","\\emptysetoarr")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EMPTY SET WITH RIGHT ARROW ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10676', commands :: [(Text, Text)]
commands = [("unicode-math","\\emptysetoarrl")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "EMPTY SET WITH LEFT ARROW ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10677', commands :: [(Text, Text)]
commands = [("unicode-math","\\circlehbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLE WITH HORIZONTAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10678', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED VERTICAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10679', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledparallel")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED PARALLEL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10680', commands :: [(Text, Text)]
commands = [("txfonts","\\circledbslash"),("unicode-math","\\obslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED REVERSE SOLIDUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10681', commands :: [(Text, Text)]
commands = [("unicode-math","\\operp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED PERPENDICULAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10682', commands :: [(Text, Text)]
commands = [("unicode-math","\\obot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLE DIVIDED BY HORIZONTAL BAR AND TOP HALF DIVIDED BY VERTICAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10683', commands :: [(Text, Text)]
commands = [("unicode-math","\\olcross")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLE WITH SUPERIMPOSED X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10684', commands :: [(Text, Text)]
commands = [("unicode-math","\\odotslashdot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLED ANTICLOCKWISE-ROTATED DIVISION SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10685', commands :: [(Text, Text)]
commands = [("unicode-math","\\uparrowoncircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UP ARROW THROUGH CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10686', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledwhitebullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLED WHITE BULLET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10687', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledbullet")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLED BULLET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10688', commands :: [(Text, Text)]
commands = [("txfonts","\\circledless"),("unicode-math","\\olessthan")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10689', commands :: [(Text, Text)]
commands = [("txfonts","\\circledgtr"),("unicode-math","\\ogreaterthan")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10690', commands :: [(Text, Text)]
commands = [("unicode-math","\\cirscir")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLE WITH SMALL CIRCLE TO THE RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10691', commands :: [(Text, Text)]
commands = [("unicode-math","\\cirE")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "CIRCLE WITH TWO HORIZONTAL STROKES TO THE RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10692', commands :: [(Text, Text)]
commands = [("stmaryrd","\\boxslash"),("txfonts","\\boxslash"),("unicode-math","\\boxdiag")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SQUARED RISING DIAGONAL SLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10693', commands :: [(Text, Text)]
commands = [("stmaryrd","\\boxbslash"),("txfonts","\\boxbslash"),("unicode-math","\\boxbslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SQUARED FALLING DIAGONAL SLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10694', commands :: [(Text, Text)]
commands = [("stmaryrd","\\boxast"),("txfonts","\\boxast"),("unicode-math","\\boxast")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SQUARED ASTERISK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10695', commands :: [(Text, Text)]
commands = [("stmaryrd","\\boxcircle"),("unicode-math","\\boxcircle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SQUARED SMALL CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10696', commands :: [(Text, Text)]
commands = [("stmaryrd","\\boxbox"),("unicode-math","\\boxbox")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SQUARED SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10697', commands :: [(Text, Text)]
commands = [("unicode-math","\\boxonbox")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TWO JOINED SQUARES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10698', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangleodot")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TRIANGLE WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10699', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangleubar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TRIANGLE WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10700', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangles")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "S IN TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10701', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangleserifs")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TRIANGLE WITH SERIFS AT BOTTOM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10702', commands :: [(Text, Text)]
commands = [("unicode-math","\\rtriltri")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHT TRIANGLE ABOVE LEFT TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10703', commands :: [(Text, Text)]
commands = [("wrisym","\\LeftTriangleBar"),("unicode-math","\\ltrivb")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT TRIANGLE BESIDE VERTICAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10704', commands :: [(Text, Text)]
commands = [("wrisym","\\RightTriangleBar"),("unicode-math","\\vbrtri")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "VERTICAL BAR BESIDE RIGHT TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10705', commands :: [(Text, Text)]
commands = [("unicode-math","\\lfbowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left black bowtie"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10706', commands :: [(Text, Text)]
commands = [("unicode-math","\\rfbowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right black bowtie"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10707', commands :: [(Text, Text)]
commands = [("unicode-math","\\fbowtie")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "BLACK BOWTIE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10708', commands :: [(Text, Text)]
commands = [("unicode-math","\\lftimes")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "left black times"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10709', commands :: [(Text, Text)]
commands = [("unicode-math","\\rftimes")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "right black times"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10710', commands :: [(Text, Text)]
commands = [("unicode-math","\\hourglass")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE HOURGLASS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10711', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackhourglass")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "BLACK HOURGLASS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10712', commands :: [(Text, Text)]
commands = [("unicode-math","\\lvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT WIGGLY FENCE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10713', commands :: [(Text, Text)]
commands = [("unicode-math","\\rvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT WIGGLY FENCE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10714', commands :: [(Text, Text)]
commands = [("unicode-math","\\Lvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT DOUBLE WIGGLY FENCE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10715', commands :: [(Text, Text)]
commands = [("unicode-math","\\Rvzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT DOUBLE WIGGLY FENCE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10716', commands :: [(Text, Text)]
commands = [("unicode-math","\\iinfin")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INCOMPLETE INFINITY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10717', commands :: [(Text, Text)]
commands = [("unicode-math","\\tieinfty")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "TIE OVER INFINITY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10718', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvinfty")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "INFINITY NEGATED WITH VERTICAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10719', commands :: [(Text, Text)]
commands = [("txfonts","\\multimapboth"),("unicode-math","\\dualmap")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE-ENDED MULTIMAP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10720', commands :: [(Text, Text)]
commands = [("unicode-math","\\laplac")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE WITH CONTOURED OUTLINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10721', commands :: [(Text, Text)]
commands = [("unicode-math","\\lrtriangleeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "INCREASES AS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10722', commands :: [(Text, Text)]
commands = [("unicode-math","\\shuffle")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SHUFFLE PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10723', commands :: [(Text, Text)]
commands = [("unicode-math","\\eparsl")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN AND SLANTED PARALLEL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10724', commands :: [(Text, Text)]
commands = [("unicode-math","\\smeparsl")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN AND SLANTED PARALLEL WITH TILDE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10725', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqvparsl")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "IDENTICAL TO AND SLANTED PARALLEL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10726', commands :: [(Text, Text)]
commands = [("unicode-math","\\gleichstark")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GLEICH STARK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10727', commands :: [(Text, Text)]
commands = [("unicode-math","\\thermod")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "THERMODYNAMIC"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10728', commands :: [(Text, Text)]
commands = [("unicode-math","\\downtriangleleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWN-POINTING TRIANGLE WITH LEFT HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10729', commands :: [(Text, Text)]
commands = [("unicode-math","\\downtrianglerightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWN-POINTING TRIANGLE WITH RIGHT HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10730', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackdiamonddownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK DIAMOND WITH DOWN ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10731', commands :: [(Text, Text)]
commands = [("amssymb","\\blacklozenge"),("unicode-math","\\mdlgblklozenge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "BLACK LOZENGE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10732', commands :: [(Text, Text)]
commands = [("unicode-math","\\circledownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE CIRCLE WITH DOWN ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10733', commands :: [(Text, Text)]
commands = [("unicode-math","\\blackcircledownarrow")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK CIRCLE WITH DOWN ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10734', commands :: [(Text, Text)]
commands = [("unicode-math","\\errbarsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ERROR-BARRED WHITE SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10735', commands :: [(Text, Text)]
commands = [("unicode-math","\\errbarblacksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ERROR-BARRED BLACK SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10736', commands :: [(Text, Text)]
commands = [("unicode-math","\\errbardiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ERROR-BARRED WHITE DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10737', commands :: [(Text, Text)]
commands = [("unicode-math","\\errbarblackdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ERROR-BARRED BLACK DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10738', commands :: [(Text, Text)]
commands = [("unicode-math","\\errbarcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ERROR-BARRED WHITE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10739', commands :: [(Text, Text)]
commands = [("unicode-math","\\errbarblackcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "ERROR-BARRED BLACK CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10740', commands :: [(Text, Text)]
commands = [("unicode-math","\\ruledelayed")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RULE-DELAYED"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10741', commands :: [(Text, Text)]
commands = [("base","\\setminus"),("unicode-math","\\setminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "REVERSE SOLIDUS OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10742', commands :: [(Text, Text)]
commands = [("unicode-math","\\dsol")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SOLIDUS WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10743', commands :: [(Text, Text)]
commands = [("unicode-math","\\rsolbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "REVERSE SOLIDUS WITH HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10744', commands :: [(Text, Text)]
commands = [("unicode-math","\\xsol")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "BIG SOLIDUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10745', commands :: [(Text, Text)]
commands = [("oz","\\zhide"),("oz","\\hide"),("unicode-math","\\xbsol")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "BIG REVERSE SOLIDUS, z notation schema hiding"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10746', commands :: [(Text, Text)]
commands = [("unicode-math","\\doubleplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOUBLE PLUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10747', commands :: [(Text, Text)]
commands = [("unicode-math","\\tripleplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TRIPLE PLUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10748', commands :: [(Text, Text)]
commands = [("unicode-math","\\lcurvyangle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "left pointing curved angle bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10749', commands :: [(Text, Text)]
commands = [("unicode-math","\\rcurvyangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "right pointing curved angle bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10750', commands :: [(Text, Text)]
commands = [("unicode-math","\\tplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TINY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10751', commands :: [(Text, Text)]
commands = [("unicode-math","\\tminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINY"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10752', commands :: [(Text, Text)]
commands = [("base","\\bigodot"),("unicode-math","\\bigodot")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY CIRCLED DOT OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10753', commands :: [(Text, Text)]
commands = [("base","\\bigoplus"),("unicode-math","\\bigoplus")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY CIRCLED PLUS OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10754', commands :: [(Text, Text)]
commands = [("base","\\bigotimes"),("unicode-math","\\bigotimes")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY CIRCLED TIMES OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10755', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigcupdot")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY UNION OPERATOR WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10756', commands :: [(Text, Text)]
commands = [("base","\\biguplus"),("unicode-math","\\biguplus")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY UNION OPERATOR WITH PLUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10757', commands :: [(Text, Text)]
commands = [("txfonts","\\bigsqcap"),("unicode-math","\\bigsqcap")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY SQUARE INTERSECTION OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10758', commands :: [(Text, Text)]
commands = [("base","\\bigsqcup"),("unicode-math","\\bigsqcup")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY SQUARE UNION OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10759', commands :: [(Text, Text)]
commands = [("unicode-math","\\conjquant")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "TWO LOGICAL AND OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10760', commands :: [(Text, Text)]
commands = [("unicode-math","\\disjquant")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "TWO LOGICAL OR OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10761', commands :: [(Text, Text)]
commands = [("txfonts","\\varprod"),("unicode-math","\\bigtimes")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY TIMES OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10762', commands :: [(Text, Text)]
commands = [("unicode-math","\\modtwosum")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MODULO TWO SUM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10763', commands :: [(Text, Text)]
commands = [("unicode-math","\\sumint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "SUMMATION WITH INTEGRAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10764', commands :: [(Text, Text)]
commands = [("amsmath","\\iiiint"),("esint","\\iiiint"),("unicode-math","\\iiiint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "QUADRUPLE INTEGRAL OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10765', commands :: [(Text, Text)]
commands = [("unicode-math","\\intbar")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "FINITE PART INTEGRAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10766', commands :: [(Text, Text)]
commands = [("unicode-math","\\intBar")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL WITH DOUBLE STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10767', commands :: [(Text, Text)]
commands = [("esint","\\fint"),("wrisym","\\fint"),("unicode-math","\\fint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL AVERAGE WITH SLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10768', commands :: [(Text, Text)]
commands = [("unicode-math","\\cirfnint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "CIRCULATION FUNCTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10769', commands :: [(Text, Text)]
commands = [("unicode-math","\\awint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "ANTICLOCKWISE INTEGRATION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10770', commands :: [(Text, Text)]
commands = [("unicode-math","\\rppolint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LINE INTEGRATION WITH RECTANGULAR PATH AROUND POLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10771', commands :: [(Text, Text)]
commands = [("unicode-math","\\scpolint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LINE INTEGRATION WITH SEMICIRCULAR PATH AROUND POLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10772', commands :: [(Text, Text)]
commands = [("unicode-math","\\npolint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LINE INTEGRATION NOT INCLUDING THE POLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10773', commands :: [(Text, Text)]
commands = [("unicode-math","\\pointint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL AROUND A POINT OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10774', commands :: [(Text, Text)]
commands = [("esint","\\sqint"),("wrisym","\\sqrint"),("unicode-math","\\sqint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "QUATERNION INTEGRAL OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10775', commands :: [(Text, Text)]
commands = [("unicode-math","\\intlarhk")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL WITH LEFTWARDS ARROW WITH HOOK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10776', commands :: [(Text, Text)]
commands = [("unicode-math","\\intx")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL WITH TIMES SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10777', commands :: [(Text, Text)]
commands = [("unicode-math","\\intcap")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL WITH INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10778', commands :: [(Text, Text)]
commands = [("unicode-math","\\intcup")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL WITH UNION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10779', commands :: [(Text, Text)]
commands = [("unicode-math","\\upint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10780', commands :: [(Text, Text)]
commands = [("unicode-math","\\lowint")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "INTEGRAL WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10781', commands :: [(Text, Text)]
commands = [("amssymb","\\Join"),("unicode-math","\\Join")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "JOIN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10782', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigtriangleleft")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LARGE LEFT TRIANGLE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10783', commands :: [(Text, Text)]
commands = [("oz","\\zcmp"),("oz","\\semi"),("unicode-math","\\zcmp")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "= \\fatsemi (stmaryrd), Z NOTATION SCHEMA COMPOSITION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10784', commands :: [(Text, Text)]
commands = [("oz","\\zpipe"),("unicode-math","\\zpipe")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "Z NOTATION SCHEMA PIPING"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10785', commands :: [(Text, Text)]
commands = [("oz","\\zproject"),("oz","\\project"),("unicode-math","\\zproject")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "Z NOTATION SCHEMA PROJECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10786', commands :: [(Text, Text)]
commands = [("unicode-math","\\ringplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN WITH SMALL CIRCLE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10787', commands :: [(Text, Text)]
commands = [("unicode-math","\\plushat")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN WITH CIRCUMFLEX ACCENT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10788', commands :: [(Text, Text)]
commands = [("unicode-math","\\simplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN WITH TILDE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10789', commands :: [(Text, Text)]
commands = [("unicode-math","\\plusdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN WITH DOT BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10790', commands :: [(Text, Text)]
commands = [("unicode-math","\\plussim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN WITH TILDE BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10791', commands :: [(Text, Text)]
commands = [("unicode-math","\\plussubtwo")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN WITH SUBSCRIPT TWO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10792', commands :: [(Text, Text)]
commands = [("unicode-math","\\plustrif")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN WITH BLACK TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10793', commands :: [(Text, Text)]
commands = [("unicode-math","\\commaminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINUS SIGN WITH COMMA ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10794', commands :: [(Text, Text)]
commands = [("unicode-math","\\minusdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINUS SIGN WITH DOT BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10795', commands :: [(Text, Text)]
commands = [("unicode-math","\\minusfdots")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINUS SIGN WITH FALLING DOTS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10796', commands :: [(Text, Text)]
commands = [("unicode-math","\\minusrdots")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINUS SIGN WITH RISING DOTS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10797', commands :: [(Text, Text)]
commands = [("unicode-math","\\opluslhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN IN LEFT HALF CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10798', commands :: [(Text, Text)]
commands = [("unicode-math","\\oplusrhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN IN RIGHT HALF CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10799', commands :: [(Text, Text)]
commands = [("base","\\times"),("unicode-math","\\vectimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "VECTOR OR CROSS PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10800', commands :: [(Text, Text)]
commands = [("unicode-math","\\dottimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTIPLICATION SIGN WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10801', commands :: [(Text, Text)]
commands = [("unicode-math","\\timesbar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTIPLICATION SIGN WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10802', commands :: [(Text, Text)]
commands = [("unicode-math","\\btimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SEMIDIRECT PRODUCT WITH BOTTOM CLOSED"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10803', commands :: [(Text, Text)]
commands = [("unicode-math","\\smashtimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SMASH PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10804', commands :: [(Text, Text)]
commands = [("unicode-math","\\otimeslhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTIPLICATION SIGN IN LEFT HALF CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10805', commands :: [(Text, Text)]
commands = [("unicode-math","\\otimesrhrim")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTIPLICATION SIGN IN RIGHT HALF CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10806', commands :: [(Text, Text)]
commands = [("unicode-math","\\otimeshat")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED MULTIPLICATION SIGN WITH CIRCUMFLEX ACCENT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10807', commands :: [(Text, Text)]
commands = [("unicode-math","\\Otimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTIPLICATION SIGN IN DOUBLE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10808', commands :: [(Text, Text)]
commands = [("unicode-math","\\odiv")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CIRCLED DIVISION SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10809', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangleplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN IN TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10810', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangleminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MINUS SIGN IN TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10811', commands :: [(Text, Text)]
commands = [("unicode-math","\\triangletimes")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "MULTIPLICATION SIGN IN TRIANGLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10812', commands :: [(Text, Text)]
commands = [("unicode-math","\\intprod")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERIOR PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10813', commands :: [(Text, Text)]
commands = [("unicode-math","\\intprodr")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "RIGHTHAND INTERIOR PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10814', commands :: [(Text, Text)]
commands = [("oz","\\fcmp"),("oz","\\comp"),("unicode-math","\\fcmp")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "Z NOTATION RELATIONAL COMPOSITION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10815', commands :: [(Text, Text)]
commands = [("base","\\amalg"),("unicode-math","\\amalg")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "AMALGAMATION OR COPRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10816', commands :: [(Text, Text)]
commands = [("unicode-math","\\capdot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERSECTION WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10817', commands :: [(Text, Text)]
commands = [("unicode-math","\\uminus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "UNION WITH MINUS SIGN, z notation bag subtraction"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10818', commands :: [(Text, Text)]
commands = [("unicode-math","\\barcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "UNION WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10819', commands :: [(Text, Text)]
commands = [("unicode-math","\\barcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERSECTION WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10820', commands :: [(Text, Text)]
commands = [("unicode-math","\\capwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERSECTION WITH LOGICAL AND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10821', commands :: [(Text, Text)]
commands = [("unicode-math","\\cupvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "UNION WITH LOGICAL OR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10822', commands :: [(Text, Text)]
commands = [("unicode-math","\\cupovercap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "UNION ABOVE INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10823', commands :: [(Text, Text)]
commands = [("unicode-math","\\capovercup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERSECTION ABOVE UNION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10824', commands :: [(Text, Text)]
commands = [("unicode-math","\\cupbarcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "UNION ABOVE BAR ABOVE INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10825', commands :: [(Text, Text)]
commands = [("unicode-math","\\capbarcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERSECTION ABOVE BAR ABOVE UNION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10826', commands :: [(Text, Text)]
commands = [("unicode-math","\\twocups")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "UNION BESIDE AND JOINED WITH UNION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10827', commands :: [(Text, Text)]
commands = [("unicode-math","\\twocaps")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "INTERSECTION BESIDE AND JOINED WITH INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10828', commands :: [(Text, Text)]
commands = [("unicode-math","\\closedvarcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CLOSED UNION WITH SERIFS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10829', commands :: [(Text, Text)]
commands = [("unicode-math","\\closedvarcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CLOSED INTERSECTION WITH SERIFS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10830', commands :: [(Text, Text)]
commands = [("unicode-math","\\Sqcap")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOUBLE SQUARE INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10831', commands :: [(Text, Text)]
commands = [("unicode-math","\\Sqcup")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOUBLE SQUARE UNION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10832', commands :: [(Text, Text)]
commands = [("unicode-math","\\closedvarcupsmashprod")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "CLOSED UNION WITH SERIFS AND SMASH PRODUCT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10833', commands :: [(Text, Text)]
commands = [("unicode-math","\\wedgeodot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL AND WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10834', commands :: [(Text, Text)]
commands = [("unicode-math","\\veeodot")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL OR WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10835', commands :: [(Text, Text)]
commands = [("unicode-math","\\Wedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOUBLE LOGICAL AND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10836', commands :: [(Text, Text)]
commands = [("unicode-math","\\Vee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOUBLE LOGICAL OR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10837', commands :: [(Text, Text)]
commands = [("unicode-math","\\wedgeonwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TWO INTERSECTING LOGICAL AND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10838', commands :: [(Text, Text)]
commands = [("unicode-math","\\veeonvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TWO INTERSECTING LOGICAL OR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10839', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigslopedvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SLOPING LARGE OR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10840', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigslopedwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SLOPING LARGE AND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10841', commands :: [(Text, Text)]
commands = [("unicode-math","\\veeonwedge")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LOGICAL OR OVERLAPPING LOGICAL AND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10842', commands :: [(Text, Text)]
commands = [("unicode-math","\\wedgemidvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL AND WITH MIDDLE STEM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10843', commands :: [(Text, Text)]
commands = [("unicode-math","\\veemidvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL OR WITH MIDDLE STEM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10844', commands :: [(Text, Text)]
commands = [("unicode-math","\\midbarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "ogical and with horizontal dash"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10845', commands :: [(Text, Text)]
commands = [("unicode-math","\\midbarvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL OR WITH HORIZONTAL DASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10846', commands :: [(Text, Text)]
commands = [("amssymb","\\doublebarwedge"),("unicode-math","\\doublebarwedge")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL AND WITH DOUBLE OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10847', commands :: [(Text, Text)]
commands = [("unicode-math","\\wedgebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL AND WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10848', commands :: [(Text, Text)]
commands = [("unicode-math","\\wedgedoublebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL AND WITH DOUBLE UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10849', commands :: [(Text, Text)]
commands = [("unicode-math","\\varveebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "SMALL VEE WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10850', commands :: [(Text, Text)]
commands = [("unicode-math","\\doublebarvee")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL OR WITH DOUBLE OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10851', commands :: [(Text, Text)]
commands = [("unicode-math","\\veedoublebar")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "LOGICAL OR WITH DOUBLE UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10852', commands :: [(Text, Text)]
commands = [("oz","\\dsub"),("oz","\\ndres"),("unicode-math","\\dsub")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "Z NOTATION DOMAIN ANTIRESTRICTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10853', commands :: [(Text, Text)]
commands = [("oz","\\rsub"),("oz","\\nrres"),("unicode-math","\\rsub")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "Z NOTATION RANGE ANTIRESTRICTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10854', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN WITH DOT BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10855', commands :: [(Text, Text)]
commands = [("unicode-math","\\dotequiv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "IDENTICAL WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10856', commands :: [(Text, Text)]
commands = [("unicode-math","\\equivVert")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TRIPLE HORIZONTAL BAR WITH DOUBLE VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10857', commands :: [(Text, Text)]
commands = [("unicode-math","\\equivVvert")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TRIPLE HORIZONTAL BAR WITH TRIPLE VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10858', commands :: [(Text, Text)]
commands = [("unicode-math","\\dotsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TILDE OPERATOR WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10859', commands :: [(Text, Text)]
commands = [("unicode-math","\\simrdots")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TILDE OPERATOR WITH RISING DOTS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10860', commands :: [(Text, Text)]
commands = [("unicode-math","\\simminussim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SIMILAR MINUS SIMILAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10861', commands :: [(Text, Text)]
commands = [("unicode-math","\\congdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CONGRUENT WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10862', commands :: [(Text, Text)]
commands = [("unicode-math","\\asteq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS WITH ASTERISK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10863', commands :: [(Text, Text)]
commands = [("unicode-math","\\hatapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ALMOST EQUAL TO WITH CIRCUMFLEX ACCENT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10864', commands :: [(Text, Text)]
commands = [("unicode-math","\\approxeqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "APPROXIMATELY EQUAL OR EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10865', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqqplus")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "EQUALS SIGN ABOVE PLUS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10866', commands :: [(Text, Text)]
commands = [("unicode-math","\\pluseqq")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "PLUS SIGN ABOVE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10867', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqqsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN ABOVE TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10868', commands :: [(Text, Text)]
commands = [("txfonts","\\Coloneqq"),("base","::="),("unicode-math","\\Coloneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "x \\Coloneq (txfonts), DOUBLE COLON EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10869', commands :: [(Text, Text)]
commands = [("wrisym","\\Equal"),("base","=="),("unicode-math","\\eqeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TWO CONSECUTIVE EQUALS SIGNS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10870', commands :: [(Text, Text)]
commands = [("wrisym","\\Same"),("base","==="),("unicode-math","\\eqeqeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "THREE CONSECUTIVE EQUALS SIGNS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10871', commands :: [(Text, Text)]
commands = [("unicode-math","\\ddotseq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN WITH TWO DOTS ABOVE AND TWO DOTS BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10872', commands :: [(Text, Text)]
commands = [("unicode-math","\\equivDD")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUIVALENT WITH FOUR DOTS ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10873', commands :: [(Text, Text)]
commands = [("unicode-math","\\ltcir")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN WITH CIRCLE INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10874', commands :: [(Text, Text)]
commands = [("unicode-math","\\gtcir")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN WITH CIRCLE INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10875', commands :: [(Text, Text)]
commands = [("unicode-math","\\ltquest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN WITH QUESTION MARK ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10876', commands :: [(Text, Text)]
commands = [("unicode-math","\\gtquest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN WITH QUESTION MARK ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10877', commands :: [(Text, Text)]
commands = [("amssymb","\\leqslant"),("fourier","\\leqslant"),("unicode-math","\\leqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN OR SLANTED EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10878', commands :: [(Text, Text)]
commands = [("amssymb","\\geqslant"),("fourier","\\geqslant"),("unicode-math","\\geqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN OR SLANTED EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10879', commands :: [(Text, Text)]
commands = [("unicode-math","\\lesdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN OR SLANTED EQUAL TO WITH DOT INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10880', commands :: [(Text, Text)]
commands = [("unicode-math","\\gesdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN OR SLANTED EQUAL TO WITH DOT INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10881', commands :: [(Text, Text)]
commands = [("unicode-math","\\lesdoto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN OR SLANTED EQUAL TO WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10882', commands :: [(Text, Text)]
commands = [("unicode-math","\\gesdoto")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN OR SLANTED EQUAL TO WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10883', commands :: [(Text, Text)]
commands = [("unicode-math","\\lesdotor")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN OR SLANTED EQUAL TO WITH DOT ABOVE RIGHT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10884', commands :: [(Text, Text)]
commands = [("unicode-math","\\gesdotol")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN OR SLANTED EQUAL TO WITH DOT ABOVE LEFT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10885', commands :: [(Text, Text)]
commands = [("amssymb","\\lessapprox"),("unicode-math","\\lessapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN OR APPROXIMATE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10886', commands :: [(Text, Text)]
commands = [("amssymb","\\gtrapprox"),("unicode-math","\\gtrapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN OR APPROXIMATE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10887', commands :: [(Text, Text)]
commands = [("amssymb","\\lneq"),("unicode-math","\\lneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN AND SINGLE-LINE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10888', commands :: [(Text, Text)]
commands = [("amssymb","\\gneq"),("unicode-math","\\gneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN AND SINGLE-LINE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10889', commands :: [(Text, Text)]
commands = [("amssymb","\\lnapprox"),("unicode-math","\\lnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN AND NOT APPROXIMATE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10890', commands :: [(Text, Text)]
commands = [("amssymb","\\gnapprox"),("unicode-math","\\gnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN AND NOT APPROXIMATE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10891', commands :: [(Text, Text)]
commands = [("amssymb","\\lesseqqgtr"),("unicode-math","\\lesseqqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN ABOVE DOUBLE-LINE EQUAL ABOVE GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10892', commands :: [(Text, Text)]
commands = [("amssymb","\\gtreqqless"),("unicode-math","\\gtreqqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN ABOVE DOUBLE-LINE EQUAL ABOVE LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10893', commands :: [(Text, Text)]
commands = [("unicode-math","\\lsime")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN ABOVE SIMILAR OR EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10894', commands :: [(Text, Text)]
commands = [("unicode-math","\\gsime")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN ABOVE SIMILAR OR EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10895', commands :: [(Text, Text)]
commands = [("unicode-math","\\lsimg")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN ABOVE SIMILAR ABOVE GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10896', commands :: [(Text, Text)]
commands = [("unicode-math","\\gsiml")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN ABOVE SIMILAR ABOVE LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10897', commands :: [(Text, Text)]
commands = [("unicode-math","\\lgE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN ABOVE GREATER-THAN ABOVE DOUBLE-LINE EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10898', commands :: [(Text, Text)]
commands = [("unicode-math","\\glE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN ABOVE LESS-THAN ABOVE DOUBLE-LINE EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10899', commands :: [(Text, Text)]
commands = [("unicode-math","\\lesges")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN ABOVE SLANTED EQUAL ABOVE GREATER-THAN ABOVE SLANTED EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10900', commands :: [(Text, Text)]
commands = [("unicode-math","\\gesles")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN ABOVE SLANTED EQUAL ABOVE LESS-THAN ABOVE SLANTED EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10901', commands :: [(Text, Text)]
commands = [("amssymb","\\eqslantless"),("unicode-math","\\eqslantless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SLANTED EQUAL TO OR LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10902', commands :: [(Text, Text)]
commands = [("amssymb","\\eqslantgtr"),("unicode-math","\\eqslantgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SLANTED EQUAL TO OR GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10903', commands :: [(Text, Text)]
commands = [("unicode-math","\\elsdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SLANTED EQUAL TO OR LESS-THAN WITH DOT INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10904', commands :: [(Text, Text)]
commands = [("unicode-math","\\egsdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SLANTED EQUAL TO OR GREATER-THAN WITH DOT INSIDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10905', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqqless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE-LINE EQUAL TO OR LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10906', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqqgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE-LINE EQUAL TO OR GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10907', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqqslantless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE-LINE SLANTED EQUAL TO OR LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10908', commands :: [(Text, Text)]
commands = [("unicode-math","\\eqqslantgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE-LINE SLANTED EQUAL TO OR GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10909', commands :: [(Text, Text)]
commands = [("unicode-math","\\simless")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SIMILAR OR LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10910', commands :: [(Text, Text)]
commands = [("unicode-math","\\simgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SIMILAR OR GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10911', commands :: [(Text, Text)]
commands = [("unicode-math","\\simlE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SIMILAR ABOVE LESS-THAN ABOVE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10912', commands :: [(Text, Text)]
commands = [("unicode-math","\\simgE")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SIMILAR ABOVE GREATER-THAN ABOVE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10913', commands :: [(Text, Text)]
commands = [("wrisym","\\NestedLessLess"),("mathabx -amssymb","\\lll"),("unicode-math","\\Lt")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE NESTED LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10914', commands :: [(Text, Text)]
commands = [("wrisym","\\NestedGreaterGreater"),("mathabx -amssymb","\\ggg"),("unicode-math","\\Gt")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE NESTED GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10915', commands :: [(Text, Text)]
commands = [("unicode-math","\\partialmeetcontraction")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "double less-than with underbar"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10916', commands :: [(Text, Text)]
commands = [("unicode-math","\\glj")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN OVERLAPPING LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10917', commands :: [(Text, Text)]
commands = [("unicode-math","\\gla")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN BESIDE LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10918', commands :: [(Text, Text)]
commands = [("stmaryrd","\\leftslice"),("unicode-math","\\ltcc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN CLOSED BY CURVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10919', commands :: [(Text, Text)]
commands = [("stmaryrd","\\rightslice"),("unicode-math","\\gtcc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN CLOSED BY CURVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10920', commands :: [(Text, Text)]
commands = [("unicode-math","\\lescc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LESS-THAN CLOSED BY CURVE ABOVE SLANTED EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10921', commands :: [(Text, Text)]
commands = [("unicode-math","\\gescc")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "GREATER-THAN CLOSED BY CURVE ABOVE SLANTED EQUAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10922', commands :: [(Text, Text)]
commands = [("unicode-math","\\smt")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SMALLER THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10923', commands :: [(Text, Text)]
commands = [("unicode-math","\\lat")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LARGER THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10924', commands :: [(Text, Text)]
commands = [("unicode-math","\\smte")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SMALLER THAN OR EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10925', commands :: [(Text, Text)]
commands = [("unicode-math","\\late")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LARGER THAN OR EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10926', commands :: [(Text, Text)]
commands = [("unicode-math","\\bumpeqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN WITH BUMPY ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10927', commands :: [(Text, Text)]
commands = [("base","\\preceq"),("unicode-math","\\preceq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PRECEDES ABOVE SINGLE-LINE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10928', commands :: [(Text, Text)]
commands = [("base","\\succeq"),("unicode-math","\\succeq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS ABOVE SINGLE-LINE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10929', commands :: [(Text, Text)]
commands = [("unicode-math","\\precneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PRECEDES ABOVE SINGLE-LINE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10930', commands :: [(Text, Text)]
commands = [("unicode-math","\\succneq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS ABOVE SINGLE-LINE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10931', commands :: [(Text, Text)]
commands = [("txfonts","\\preceqq"),("unicode-math","\\preceqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PRECEDES ABOVE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10932', commands :: [(Text, Text)]
commands = [("txfonts","\\succeqq"),("unicode-math","\\succeqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS ABOVE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10933', commands :: [(Text, Text)]
commands = [("unicode-math","\\precneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PRECEDES ABOVE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10934', commands :: [(Text, Text)]
commands = [("unicode-math","\\succneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS ABOVE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10935', commands :: [(Text, Text)]
commands = [("amssymb","\\precapprox"),("unicode-math","\\precapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PRECEDES ABOVE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10936', commands :: [(Text, Text)]
commands = [("amssymb","\\succapprox"),("unicode-math","\\succapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS ABOVE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10937', commands :: [(Text, Text)]
commands = [("amssymb","\\precnapprox"),("unicode-math","\\precnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PRECEDES ABOVE NOT ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10938', commands :: [(Text, Text)]
commands = [("amssymb","\\succnapprox"),("unicode-math","\\succnapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUCCEEDS ABOVE NOT ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10939', commands :: [(Text, Text)]
commands = [("mathabx","\\llcurly"),("unicode-math","\\Prec")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE PRECEDES"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10940', commands :: [(Text, Text)]
commands = [("mathabx","\\ggcurly"),("unicode-math","\\Succ")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE SUCCEEDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10941', commands :: [(Text, Text)]
commands = [("unicode-math","\\subsetdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10942', commands :: [(Text, Text)]
commands = [("unicode-math","\\supsetdot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET WITH DOT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10943', commands :: [(Text, Text)]
commands = [("unicode-math","\\subsetplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET WITH PLUS SIGN BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10944', commands :: [(Text, Text)]
commands = [("unicode-math","\\supsetplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET WITH PLUS SIGN BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10945', commands :: [(Text, Text)]
commands = [("unicode-math","\\submult")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET WITH MULTIPLICATION SIGN BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10946', commands :: [(Text, Text)]
commands = [("unicode-math","\\supmult")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET WITH MULTIPLICATION SIGN BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10947', commands :: [(Text, Text)]
commands = [("unicode-math","\\subedot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET OF OR EQUAL TO WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10948', commands :: [(Text, Text)]
commands = [("unicode-math","\\supedot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET OF OR EQUAL TO WITH DOT ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10949', commands :: [(Text, Text)]
commands = [("amssymb","\\subseteqq"),("unicode-math","\\subseteqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET OF ABOVE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10950', commands :: [(Text, Text)]
commands = [("amssymb","\\supseteqq"),("unicode-math","\\supseteqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET OF ABOVE EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10951', commands :: [(Text, Text)]
commands = [("unicode-math","\\subsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET OF ABOVE TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10952', commands :: [(Text, Text)]
commands = [("unicode-math","\\supsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET OF ABOVE TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10953', commands :: [(Text, Text)]
commands = [("unicode-math","\\subsetapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET OF ABOVE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10954', commands :: [(Text, Text)]
commands = [("unicode-math","\\supsetapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET OF ABOVE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10955', commands :: [(Text, Text)]
commands = [("amssymb","\\subsetneqq"),("unicode-math","\\subsetneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET OF ABOVE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10956', commands :: [(Text, Text)]
commands = [("amssymb","\\supsetneqq"),("unicode-math","\\supsetneqq")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET OF ABOVE NOT EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10957', commands :: [(Text, Text)]
commands = [("unicode-math","\\lsqhook")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SQUARE LEFT OPEN BOX OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10958', commands :: [(Text, Text)]
commands = [("unicode-math","\\rsqhook")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SQUARE RIGHT OPEN BOX OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10959', commands :: [(Text, Text)]
commands = [("unicode-math","\\csub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CLOSED SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10960', commands :: [(Text, Text)]
commands = [("unicode-math","\\csup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CLOSED SUPERSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10961', commands :: [(Text, Text)]
commands = [("unicode-math","\\csube")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CLOSED SUBSET OR EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10962', commands :: [(Text, Text)]
commands = [("unicode-math","\\csupe")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "CLOSED SUPERSET OR EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10963', commands :: [(Text, Text)]
commands = [("unicode-math","\\subsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET ABOVE SUPERSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10964', commands :: [(Text, Text)]
commands = [("unicode-math","\\supsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET ABOVE SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10965', commands :: [(Text, Text)]
commands = [("unicode-math","\\subsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUBSET ABOVE SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10966', commands :: [(Text, Text)]
commands = [("unicode-math","\\supsup")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET ABOVE SUPERSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10967', commands :: [(Text, Text)]
commands = [("unicode-math","\\suphsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET BESIDE SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10968', commands :: [(Text, Text)]
commands = [("unicode-math","\\supdsub")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SUPERSET BESIDE AND JOINED BY DASH WITH SUBSET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10969', commands :: [(Text, Text)]
commands = [("unicode-math","\\forkv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "ELEMENT OF OPENING DOWNWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10970', commands :: [(Text, Text)]
commands = [("unicode-math","\\topfork")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PITCHFORK WITH TEE TOP"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10971', commands :: [(Text, Text)]
commands = [("unicode-math","\\mlcp")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TRANSVERSAL INTERSECTION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10972', commands :: [(Text, Text)]
commands = [("unicode-math","\\forks")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "FORKING"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10973', commands :: [(Text, Text)]
commands = [("unicode-math","\\forksnot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "NONFORKING"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10974', commands :: [(Text, Text)]
commands = [("unicode-math","\\shortlefttack")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SHORT LEFT TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10975', commands :: [(Text, Text)]
commands = [("unicode-math","\\shortdowntack")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SHORT DOWN TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10976', commands :: [(Text, Text)]
commands = [("unicode-math","\\shortuptack")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SHORT UP TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10977', commands :: [(Text, Text)]
commands = [("unicode-math","\\perps")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "PERPENDICULAR WITH S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10978', commands :: [(Text, Text)]
commands = [("unicode-math","\\vDdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "VERTICAL BAR TRIPLE RIGHT TURNSTILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10979', commands :: [(Text, Text)]
commands = [("unicode-math","\\dashV")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE VERTICAL BAR LEFT TURNSTILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10980', commands :: [(Text, Text)]
commands = [("unicode-math","\\Dashv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "VERTICAL BAR DOUBLE LEFT TURNSTILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10981', commands :: [(Text, Text)]
commands = [("unicode-math","\\DashV")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE VERTICAL BAR DOUBLE LEFT TURNSTILE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10982', commands :: [(Text, Text)]
commands = [("unicode-math","\\varVdash")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG DASH FROM LEFT MEMBER OF DOUBLE VERTICAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10983', commands :: [(Text, Text)]
commands = [("unicode-math","\\Barv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SHORT DOWN TACK WITH OVERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10984', commands :: [(Text, Text)]
commands = [("unicode-math","\\vBar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SHORT UP TACK WITH UNDERBAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10985', commands :: [(Text, Text)]
commands = [("unicode-math","\\vBarv")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "SHORT UP TACK ABOVE SHORT DOWN TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10986', commands :: [(Text, Text)]
commands = [("txfonts","\\Top"),("unicode-math","\\barV")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE DOWN TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10987', commands :: [(Text, Text)]
commands = [("txfonts","\\Bot"),("txfonts","\\Perp"),("unicode-math","\\Vbar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE UP TACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10988', commands :: [(Text, Text)]
commands = [("unicode-math","\\Not")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE STROKE NOT SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10989', commands :: [(Text, Text)]
commands = [("unicode-math","\\bNot")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "REVERSED DOUBLE STROKE NOT SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10990', commands :: [(Text, Text)]
commands = [("unicode-math","\\revnmid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOES NOT DIVIDE WITH REVERSED NEGATION SLASH"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10991', commands :: [(Text, Text)]
commands = [("unicode-math","\\cirmid")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "VERTICAL LINE WITH CIRCLE ABOVE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10992', commands :: [(Text, Text)]
commands = [("unicode-math","\\midcir")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "VERTICAL LINE WITH CIRCLE BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10993', commands :: [(Text, Text)]
commands = [("unicode-math","\\topcir")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWN TACK WITH CIRCLE BELOW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10994', commands :: [(Text, Text)]
commands = [("unicode-math","\\nhpar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PARALLEL WITH HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10995', commands :: [(Text, Text)]
commands = [("unicode-math","\\parsim")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "PARALLEL WITH TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10996', commands :: [(Text, Text)]
commands = [("stmaryrd","\\interleave"),("unicode-math","\\interleave")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TRIPLE VERTICAL BAR BINARY RELATION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10997', commands :: [(Text, Text)]
commands = [("unicode-math","\\nhVvert")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TRIPLE VERTICAL BAR WITH HORIZONTAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10998', commands :: [(Text, Text)]
commands = [("unicode-math","\\threedotcolon")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TRIPLE COLON OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\10999', commands :: [(Text, Text)]
commands = [("unicode-math","\\lllnest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TRIPLE NESTED LESS-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11000', commands :: [(Text, Text)]
commands = [("unicode-math","\\gggnest")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TRIPLE NESTED GREATER-THAN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11001', commands :: [(Text, Text)]
commands = [("unicode-math","\\leqqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE-LINE SLANTED LESS-THAN OR EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11002', commands :: [(Text, Text)]
commands = [("unicode-math","\\geqqslant")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "DOUBLE-LINE SLANTED GREATER-THAN OR EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11003', commands :: [(Text, Text)]
commands = [("unicode-math","\\trslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "TRIPLE SOLIDUS BINARY RELATION"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11004', commands :: [(Text, Text)]
commands = [("stmaryrd","\\biginterleave"),("unicode-math","\\biginterleave")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "LARGE TRIPLE VERTICAL BAR OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11005', commands :: [(Text, Text)]
commands = [("stmaryrd","\\sslash"),("txfonts","\\varparallel"),("unicode-math","\\sslash")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "DOUBLE SOLIDUS OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11006', commands :: [(Text, Text)]
commands = [("stmaryrd","\\talloblong"),("unicode-math","\\talloblong")], category :: TeXSymbolType
category = TeXSymbolType
Bin, comments :: Text
comments = "WHITE VERTICAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11007', commands :: [(Text, Text)]
commands = [("unicode-math","\\bigtalloblong")], category :: TeXSymbolType
category = TeXSymbolType
Op, comments :: Text
comments = "N-ARY WHITE VERTICAL BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11008', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH EAST WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11009', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH WEST WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11010', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SOUTH EAST WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11011', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SOUTH WEST WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11012', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT RIGHT WHITE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11013', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFTWARDS BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11014', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UPWARDS BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11015', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOWNWARDS BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11016', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH EAST BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11017', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "NORTH WEST BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11018', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SOUTH EAST BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11019', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SOUTH WEST BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11020', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFT RIGHT BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11021', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "UP DOWN BLACK ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11022', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHTWARDS ARROW WITH TIP DOWNWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11023', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "RIGHTWARDS ARROW WITH TIP UPWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11024', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFTWARDS ARROW WITH TIP DOWNWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11025', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "LEFTWARDS ARROW WITH TIP UPWARDS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11026', commands :: [(Text, Text)]
commands = [("unicode-math","\\squaretopblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE WITH TOP HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11027', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarebotblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE WITH BOTTOM HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11028', commands :: [(Text, Text)]
commands = [("unicode-math","\\squareurblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE WITH UPPER RIGHT DIAGONAL HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11029', commands :: [(Text, Text)]
commands = [("unicode-math","\\squarellblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SQUARE WITH LOWER LEFT DIAGONAL HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11030', commands :: [(Text, Text)]
commands = [("unicode-math","\\diamondleftblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIAMOND WITH LEFT HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11031', commands :: [(Text, Text)]
commands = [("unicode-math","\\diamondrightblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIAMOND WITH RIGHT HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11032', commands :: [(Text, Text)]
commands = [("unicode-math","\\diamondtopblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIAMOND WITH TOP HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11033', commands :: [(Text, Text)]
commands = [("unicode-math","\\diamondbotblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DIAMOND WITH BOTTOM HALF BLACK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11034', commands :: [(Text, Text)]
commands = [("unicode-math","\\dottedsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "DOTTED SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11035', commands :: [(Text, Text)]
commands = [("fourier","\\blacksquare"),("unicode-math","\\lgblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK LARGE SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11036', commands :: [(Text, Text)]
commands = [("fourier","\\square"),("unicode-math","\\lgwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE LARGE SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11037', commands :: [(Text, Text)]
commands = [("amssymb","\\centerdot"),("unicode-math","\\vysmblksquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "t \\Squaredot (marvosym), BLACK VERY SMALL SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11038', commands :: [(Text, Text)]
commands = [("unicode-math","\\vysmwhtsquare")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE VERY SMALL SQUARE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11039', commands :: [(Text, Text)]
commands = [("unicode-math","\\pentagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK PENTAGON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11040', commands :: [(Text, Text)]
commands = [("unicode-math","\\pentagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE PENTAGON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11041', commands :: [(Text, Text)]
commands = [("unicode-math","\\varhexagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE HEXAGON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11042', commands :: [(Text, Text)]
commands = [("unicode-math","\\varhexagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK HEXAGON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11043', commands :: [(Text, Text)]
commands = [("unicode-math","\\hexagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HORIZONTAL BLACK HEXAGON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11044', commands :: [(Text, Text)]
commands = [("unicode-math","\\lgblkcircle")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK LARGE CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11045', commands :: [(Text, Text)]
commands = [("unicode-math","\\mdblkdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK MEDIUM DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11046', commands :: [(Text, Text)]
commands = [("unicode-math","\\mdwhtdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE MEDIUM DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11047', commands :: [(Text, Text)]
commands = [("amssymb","\\blacklozenge"),("unicode-math","\\mdblklozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK MEDIUM LOZENGE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11048', commands :: [(Text, Text)]
commands = [("amssymb","\\lozenge"),("unicode-math","\\mdwhtlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE MEDIUM LOZENGE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11049', commands :: [(Text, Text)]
commands = [("unicode-math","\\smblkdiamond")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK SMALL DIAMOND"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11050', commands :: [(Text, Text)]
commands = [("unicode-math","\\smblklozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK SMALL LOZENGE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11051', commands :: [(Text, Text)]
commands = [("unicode-math","\\smwhtlozenge")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SMALL LOZENGE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11052', commands :: [(Text, Text)]
commands = [("unicode-math","\\blkhorzoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK HORIZONTAL ELLIPSE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11053', commands :: [(Text, Text)]
commands = [("unicode-math","\\whthorzoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE HORIZONTAL ELLIPSE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11054', commands :: [(Text, Text)]
commands = [("unicode-math","\\blkvertoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK VERTICAL ELLIPSE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11055', commands :: [(Text, Text)]
commands = [("unicode-math","\\whtvertoval")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE VERTICAL ELLIPSE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11056', commands :: [(Text, Text)]
commands = [("unicode-math","\\circleonleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT ARROW WITH SMALL CIRCLE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11057', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftthreearrows")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "THREE LEFTWARDS ARROWS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11058', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowonoplus")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFT ARROW WITH CIRCLED PLUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11059', commands :: [(Text, Text)]
commands = [("unicode-math","\\longleftsquigarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LONG LEFTWARDS SQUIGGLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11060', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvtwoheadleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS TWO-HEADED ARROW WITH VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11061', commands :: [(Text, Text)]
commands = [("unicode-math","\\nVtwoheadleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS TWO-HEADED ARROW WITH DOUBLE VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11062', commands :: [(Text, Text)]
commands = [("unicode-math","\\twoheadmapsfrom")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS TWO-HEADED ARROW FROM BAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11063', commands :: [(Text, Text)]
commands = [("unicode-math","\\twoheadleftdbkarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "leftwards two-headed triple-dash arrow"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11064', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftdotarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW WITH DOTTED STEM"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11065', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW WITH TAIL WITH VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11066', commands :: [(Text, Text)]
commands = [("unicode-math","\\nVleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11067', commands :: [(Text, Text)]
commands = [("unicode-math","\\twoheadleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS TWO-HEADED ARROW WITH TAIL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11068', commands :: [(Text, Text)]
commands = [("unicode-math","\\nvtwoheadleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS TWO-HEADED ARROW WITH TAIL WITH VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11069', commands :: [(Text, Text)]
commands = [("unicode-math","\\nVtwoheadleftarrowtail")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS TWO-HEADED ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11070', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowx")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW THROUGH X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11071', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftcurvedarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "WAVE ARROW POINTING DIRECTLY LEFT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11072', commands :: [(Text, Text)]
commands = [("unicode-math","\\equalleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "EQUALS SIGN ABOVE LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11073', commands :: [(Text, Text)]
commands = [("unicode-math","\\bsimilarleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "REVERSE TILDE OPERATOR ABOVE LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11074', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowbackapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW ABOVE REVERSE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11075', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowgtr")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "rightwards arrow through less-than"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11076', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowsupset")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "rightwards arrow through subset"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11077', commands :: [(Text, Text)]
commands = [("unicode-math","\\LLeftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS QUADRUPLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11078', commands :: [(Text, Text)]
commands = [("unicode-math","\\RRightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS QUADRUPLE ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11079', commands :: [(Text, Text)]
commands = [("unicode-math","\\bsimilarrightarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "REVERSE TILDE OPERATOR ABOVE RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11080', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowbackapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "RIGHTWARDS ARROW ABOVE REVERSE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11081', commands :: [(Text, Text)]
commands = [("unicode-math","\\similarleftarrow")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "TILDE OPERATOR ABOVE LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11082', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowapprox")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW ABOVE ALMOST EQUAL TO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11083', commands :: [(Text, Text)]
commands = [("unicode-math","\\leftarrowbsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "LEFTWARDS ARROW ABOVE REVERSE TILDE OPERATOR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11084', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightarrowbsimilar")], category :: TeXSymbolType
category = TeXSymbolType
Rel, comments :: Text
comments = "righttwards arrow above reverse tilde operator"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11088', commands :: [(Text, Text)]
commands = [("unicode-math","\\medwhitestar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE MEDIUM STAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11089', commands :: [(Text, Text)]
commands = [("unicode-math","\\medblackstar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "black medium star"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11090', commands :: [(Text, Text)]
commands = [("unicode-math","\\smwhitestar")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE SMALL STAR"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11091', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightpentagonblack")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "BLACK RIGHT-POINTING PENTAGON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\11092', commands :: [(Text, Text)]
commands = [("unicode-math","\\rightpentagon")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "WHITE RIGHT-POINTING PENTAGON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12296', commands :: [(Text, Text)]
commands = [("base","\\langle")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT ANGLE BRACKET (deprecated for math use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12297', commands :: [(Text, Text)]
commands = [("base","\\rangle")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT ANGLE BRACKET (deprecated for math use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12306', commands :: [(Text, Text)]
commands = [("unicode-math","\\postalmark")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "POSTAL MARK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12308', commands :: [(Text, Text)]
commands = [("unicode-math","\\lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "left broken bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12309', commands :: [(Text, Text)]
commands = [("unicode-math","\\rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "right broken bracket"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12312', commands :: [(Text, Text)]
commands = [("unicode-math","\\Lbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT WHITE TORTOISE SHELL BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12313', commands :: [(Text, Text)]
commands = [("unicode-math","\\Rbrbrak")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT WHITE TORTOISE SHELL BRACKET"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12314', commands :: [(Text, Text)]
commands = [("stmaryrd","\\llbracket")], category :: TeXSymbolType
category = TeXSymbolType
Open, comments :: Text
comments = "LEFT WHITE SQUARE BRACKET (deprecated for math use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12315', commands :: [(Text, Text)]
commands = [("stmaryrd","\\rrbracket")], category :: TeXSymbolType
category = TeXSymbolType
Close, comments :: Text
comments = "RIGHT WHITE SQUARE BRACKET (deprecated for math use)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12336', commands :: [(Text, Text)]
commands = [("unicode-math","\\hzigzag")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "zigzag"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\12398', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "HIRAGANA LETTER NO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\64297', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HEBREW LETTER ALTERNATIVE PLUS SIGN (doesn't have cross shape)"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65024', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Accent, comments :: Text
comments = "VARIATION SELECTOR-1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65121', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SMALL ASTERISK"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65122', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SMALL PLUS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65123', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SMALL HYPHEN-MINUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65124', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SMALL LESS-THAN SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65125', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SMALL GREATER-THAN SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65126', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SMALL EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65128', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "SMALL REVERSE SOLIDUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65291', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH PLUS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65308', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH LESS-THAN SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65309', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH EQUALS SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65310', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH GREATER-THAN SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65340', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH REVERSE SOLIDUS"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65342', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH CIRCUMFLEX ACCENT"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65372', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH VERTICAL LINE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65374', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH TILDE"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65506', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "FULLWIDTH NOT SIGN"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65513', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HALFWIDTH LEFTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65514', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HALFWIDTH UPWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65515', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HALFWIDTH RIGHTWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\65516', commands :: [(Text, Text)]
commands = [], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "HALFWIDTH DOWNWARDS ARROW"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119808', commands :: [(Text, Text)]
commands = [("base","\\mathbf{A}"),("unicode-math","\\mbfA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119809', commands :: [(Text, Text)]
commands = [("base","\\mathbf{B}"),("unicode-math","\\mbfB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119810', commands :: [(Text, Text)]
commands = [("base","\\mathbf{C}"),("unicode-math","\\mbfC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119811', commands :: [(Text, Text)]
commands = [("base","\\mathbf{D}"),("unicode-math","\\mbfD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119812', commands :: [(Text, Text)]
commands = [("base","\\mathbf{E}"),("unicode-math","\\mbfE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119813', commands :: [(Text, Text)]
commands = [("base","\\mathbf{F}"),("unicode-math","\\mbfF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119814', commands :: [(Text, Text)]
commands = [("base","\\mathbf{G}"),("unicode-math","\\mbfG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119815', commands :: [(Text, Text)]
commands = [("base","\\mathbf{H}"),("unicode-math","\\mbfH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119816', commands :: [(Text, Text)]
commands = [("base","\\mathbf{I}"),("unicode-math","\\mbfI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119817', commands :: [(Text, Text)]
commands = [("base","\\mathbf{J}"),("unicode-math","\\mbfJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119818', commands :: [(Text, Text)]
commands = [("base","\\mathbf{K}"),("unicode-math","\\mbfK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119819', commands :: [(Text, Text)]
commands = [("base","\\mathbf{L}"),("unicode-math","\\mbfL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119820', commands :: [(Text, Text)]
commands = [("base","\\mathbf{M}"),("unicode-math","\\mbfM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119821', commands :: [(Text, Text)]
commands = [("base","\\mathbf{N}"),("unicode-math","\\mbfN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119822', commands :: [(Text, Text)]
commands = [("base","\\mathbf{O}"),("unicode-math","\\mbfO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119823', commands :: [(Text, Text)]
commands = [("base","\\mathbf{P}"),("unicode-math","\\mbfP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119824', commands :: [(Text, Text)]
commands = [("base","\\mathbf{Q}"),("unicode-math","\\mbfQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119825', commands :: [(Text, Text)]
commands = [("base","\\mathbf{R}"),("unicode-math","\\mbfR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119826', commands :: [(Text, Text)]
commands = [("base","\\mathbf{S}"),("unicode-math","\\mbfS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119827', commands :: [(Text, Text)]
commands = [("base","\\mathbf{T}"),("unicode-math","\\mbfT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119828', commands :: [(Text, Text)]
commands = [("base","\\mathbf{U}"),("unicode-math","\\mbfU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119829', commands :: [(Text, Text)]
commands = [("base","\\mathbf{V}"),("unicode-math","\\mbfV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119830', commands :: [(Text, Text)]
commands = [("base","\\mathbf{W}"),("unicode-math","\\mbfW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119831', commands :: [(Text, Text)]
commands = [("base","\\mathbf{X}"),("unicode-math","\\mbfX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119832', commands :: [(Text, Text)]
commands = [("base","\\mathbf{Y}"),("unicode-math","\\mbfY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119833', commands :: [(Text, Text)]
commands = [("base","\\mathbf{Z}"),("unicode-math","\\mbfZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119834', commands :: [(Text, Text)]
commands = [("base","\\mathbf{a}"),("unicode-math","\\mbfa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119835', commands :: [(Text, Text)]
commands = [("base","\\mathbf{b}"),("unicode-math","\\mbfb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119836', commands :: [(Text, Text)]
commands = [("base","\\mathbf{c}"),("unicode-math","\\mbfc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119837', commands :: [(Text, Text)]
commands = [("base","\\mathbf{d}"),("unicode-math","\\mbfd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119838', commands :: [(Text, Text)]
commands = [("base","\\mathbf{e}"),("unicode-math","\\mbfe")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119839', commands :: [(Text, Text)]
commands = [("base","\\mathbf{f}"),("unicode-math","\\mbff")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119840', commands :: [(Text, Text)]
commands = [("base","\\mathbf{g}"),("unicode-math","\\mbfg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119841', commands :: [(Text, Text)]
commands = [("base","\\mathbf{h}"),("unicode-math","\\mbfh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119842', commands :: [(Text, Text)]
commands = [("base","\\mathbf{i}"),("unicode-math","\\mbfi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119843', commands :: [(Text, Text)]
commands = [("base","\\mathbf{j}"),("unicode-math","\\mbfj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119844', commands :: [(Text, Text)]
commands = [("base","\\mathbf{k}"),("unicode-math","\\mbfk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119845', commands :: [(Text, Text)]
commands = [("base","\\mathbf{l}"),("unicode-math","\\mbfl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119846', commands :: [(Text, Text)]
commands = [("base","\\mathbf{m}"),("unicode-math","\\mbfm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119847', commands :: [(Text, Text)]
commands = [("base","\\mathbf{n}"),("unicode-math","\\mbfn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119848', commands :: [(Text, Text)]
commands = [("base","\\mathbf{o}"),("unicode-math","\\mbfo")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119849', commands :: [(Text, Text)]
commands = [("base","\\mathbf{p}"),("unicode-math","\\mbfp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119850', commands :: [(Text, Text)]
commands = [("base","\\mathbf{q}"),("unicode-math","\\mbfq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119851', commands :: [(Text, Text)]
commands = [("base","\\mathbf{r}"),("unicode-math","\\mbfr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119852', commands :: [(Text, Text)]
commands = [("base","\\mathbf{s}"),("unicode-math","\\mbfs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119853', commands :: [(Text, Text)]
commands = [("base","\\mathbf{t}"),("unicode-math","\\mbft")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119854', commands :: [(Text, Text)]
commands = [("base","\\mathbf{u}"),("unicode-math","\\mbfu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119855', commands :: [(Text, Text)]
commands = [("base","\\mathbf{v}"),("unicode-math","\\mbfv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119856', commands :: [(Text, Text)]
commands = [("base","\\mathbf{w}"),("unicode-math","\\mbfw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119857', commands :: [(Text, Text)]
commands = [("base","\\mathbf{x}"),("unicode-math","\\mbfx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119858', commands :: [(Text, Text)]
commands = [("base","\\mathbf{y}"),("unicode-math","\\mbfy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119859', commands :: [(Text, Text)]
commands = [("base","\\mathbf{z}"),("unicode-math","\\mbfz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119860', commands :: [(Text, Text)]
commands = [("base","A"),("base","\\mathit{A}"),("unicode-math","\\mitA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119861', commands :: [(Text, Text)]
commands = [("base","B"),("base","\\mathit{B}"),("unicode-math","\\mitB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119862', commands :: [(Text, Text)]
commands = [("base","C"),("base","\\mathit{C}"),("unicode-math","\\mitC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119863', commands :: [(Text, Text)]
commands = [("base","D"),("base","\\mathit{D}"),("unicode-math","\\mitD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119864', commands :: [(Text, Text)]
commands = [("base","E"),("base","\\mathit{E}"),("unicode-math","\\mitE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119865', commands :: [(Text, Text)]
commands = [("base","F"),("base","\\mathit{F}"),("unicode-math","\\mitF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119866', commands :: [(Text, Text)]
commands = [("base","G"),("base","\\mathit{G}"),("unicode-math","\\mitG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119867', commands :: [(Text, Text)]
commands = [("base","H"),("base","\\mathit{H}"),("unicode-math","\\mitH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119868', commands :: [(Text, Text)]
commands = [("base","I"),("base","\\mathit{I}"),("unicode-math","\\mitI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119869', commands :: [(Text, Text)]
commands = [("base","J"),("base","\\mathit{J}"),("unicode-math","\\mitJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119870', commands :: [(Text, Text)]
commands = [("base","K"),("base","\\mathit{K}"),("unicode-math","\\mitK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119871', commands :: [(Text, Text)]
commands = [("base","L"),("base","\\mathit{L}"),("unicode-math","\\mitL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119872', commands :: [(Text, Text)]
commands = [("base","M"),("base","\\mathit{M}"),("unicode-math","\\mitM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119873', commands :: [(Text, Text)]
commands = [("base","N"),("base","\\mathit{N}"),("unicode-math","\\mitN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119874', commands :: [(Text, Text)]
commands = [("base","O"),("base","\\mathit{O}"),("unicode-math","\\mitO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119875', commands :: [(Text, Text)]
commands = [("base","P"),("base","\\mathit{P}"),("unicode-math","\\mitP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119876', commands :: [(Text, Text)]
commands = [("base","Q"),("base","\\mathit{Q}"),("unicode-math","\\mitQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119877', commands :: [(Text, Text)]
commands = [("base","R"),("base","\\mathit{R}"),("unicode-math","\\mitR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119878', commands :: [(Text, Text)]
commands = [("base","S"),("base","\\mathit{S}"),("unicode-math","\\mitS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119879', commands :: [(Text, Text)]
commands = [("base","T"),("base","\\mathit{T}"),("unicode-math","\\mitT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119880', commands :: [(Text, Text)]
commands = [("base","U"),("base","\\mathit{U}"),("unicode-math","\\mitU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119881', commands :: [(Text, Text)]
commands = [("base","V"),("base","\\mathit{V}"),("unicode-math","\\mitV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119882', commands :: [(Text, Text)]
commands = [("base","W"),("base","\\mathit{W}"),("unicode-math","\\mitW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119883', commands :: [(Text, Text)]
commands = [("base","X"),("base","\\mathit{X}"),("unicode-math","\\mitX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119884', commands :: [(Text, Text)]
commands = [("base","Y"),("base","\\mathit{Y}"),("unicode-math","\\mitY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119885', commands :: [(Text, Text)]
commands = [("base","Z"),("base","\\mathit{Z}"),("unicode-math","\\mitZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119886', commands :: [(Text, Text)]
commands = [("base","a"),("base","\\mathit{a}"),("unicode-math","\\mita")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119887', commands :: [(Text, Text)]
commands = [("base","b"),("base","\\mathit{b}"),("unicode-math","\\mitb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119888', commands :: [(Text, Text)]
commands = [("base","c"),("base","\\mathit{c}"),("unicode-math","\\mitc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119889', commands :: [(Text, Text)]
commands = [("base","d"),("base","\\mathit{d}"),("unicode-math","\\mitd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119890', commands :: [(Text, Text)]
commands = [("base","e"),("base","\\mathit{e}"),("unicode-math","\\mite")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119891', commands :: [(Text, Text)]
commands = [("base","f"),("base","\\mathit{f}"),("unicode-math","\\mitf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119892', commands :: [(Text, Text)]
commands = [("base","g"),("base","\\mathit{g}"),("unicode-math","\\mitg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119894', commands :: [(Text, Text)]
commands = [("base","i"),("base","\\mathit{i}"),("unicode-math","\\miti")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119895', commands :: [(Text, Text)]
commands = [("base","j"),("base","\\mathit{j}"),("unicode-math","\\mitj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119896', commands :: [(Text, Text)]
commands = [("base","k"),("base","\\mathit{k}"),("unicode-math","\\mitk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119897', commands :: [(Text, Text)]
commands = [("base","l"),("base","\\mathit{l}"),("unicode-math","\\mitl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119898', commands :: [(Text, Text)]
commands = [("base","m"),("base","\\mathit{m}"),("unicode-math","\\mitm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119899', commands :: [(Text, Text)]
commands = [("base","n"),("base","\\mathit{n}"),("unicode-math","\\mitn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119900', commands :: [(Text, Text)]
commands = [("base","o"),("base","\\mathit{o}"),("unicode-math","\\mito")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119901', commands :: [(Text, Text)]
commands = [("base","p"),("base","\\mathit{p}"),("unicode-math","\\mitp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119902', commands :: [(Text, Text)]
commands = [("base","q"),("base","\\mathit{q}"),("unicode-math","\\mitq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119903', commands :: [(Text, Text)]
commands = [("base","r"),("base","\\mathit{r}"),("unicode-math","\\mitr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119904', commands :: [(Text, Text)]
commands = [("base","s"),("base","\\mathit{s}"),("unicode-math","\\mits")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119905', commands :: [(Text, Text)]
commands = [("base","t"),("base","\\mathit{t}"),("unicode-math","\\mitt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119906', commands :: [(Text, Text)]
commands = [("base","u"),("base","\\mathit{u}"),("unicode-math","\\mitu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119907', commands :: [(Text, Text)]
commands = [("base","v"),("base","\\mathit{v}"),("unicode-math","\\mitv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119908', commands :: [(Text, Text)]
commands = [("base","w"),("base","\\mathit{w}"),("unicode-math","\\mitw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119909', commands :: [(Text, Text)]
commands = [("base","x"),("base","\\mathit{x}"),("unicode-math","\\mitx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119910', commands :: [(Text, Text)]
commands = [("base","y"),("base","\\mathit{y}"),("unicode-math","\\mity")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119911', commands :: [(Text, Text)]
commands = [("base","z"),("base","\\mathit{z}"),("unicode-math","\\mitz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119912', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{A}"),("fixmath","\\mathbold{A}"),("unicode-math","\\mbfitA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119913', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{B}"),("fixmath","\\mathbold{B}"),("unicode-math","\\mbfitB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119914', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{C}"),("fixmath","\\mathbold{C}"),("unicode-math","\\mbfitC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119915', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{D}"),("fixmath","\\mathbold{D}"),("unicode-math","\\mbfitD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119916', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{E}"),("fixmath","\\mathbold{E}"),("unicode-math","\\mbfitE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119917', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{F}"),("fixmath","\\mathbold{F}"),("unicode-math","\\mbfitF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119918', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{G}"),("fixmath","\\mathbold{G}"),("unicode-math","\\mbfitG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119919', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{H}"),("fixmath","\\mathbold{H}"),("unicode-math","\\mbfitH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119920', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{I}"),("fixmath","\\mathbold{I}"),("unicode-math","\\mbfitI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119921', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{J}"),("fixmath","\\mathbold{J}"),("unicode-math","\\mbfitJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119922', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{K}"),("fixmath","\\mathbold{K}"),("unicode-math","\\mbfitK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119923', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{L}"),("fixmath","\\mathbold{L}"),("unicode-math","\\mbfitL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119924', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{M}"),("fixmath","\\mathbold{M}"),("unicode-math","\\mbfitM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119925', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{N}"),("fixmath","\\mathbold{N}"),("unicode-math","\\mbfitN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119926', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{O}"),("fixmath","\\mathbold{O}"),("unicode-math","\\mbfitO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119927', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{P}"),("fixmath","\\mathbold{P}"),("unicode-math","\\mbfitP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119928', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{Q}"),("fixmath","\\mathbold{Q}"),("unicode-math","\\mbfitQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119929', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{R}"),("fixmath","\\mathbold{R}"),("unicode-math","\\mbfitR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119930', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{S}"),("fixmath","\\mathbold{S}"),("unicode-math","\\mbfitS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119931', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{T}"),("fixmath","\\mathbold{T}"),("unicode-math","\\mbfitT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119932', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{U}"),("fixmath","\\mathbold{U}"),("unicode-math","\\mbfitU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119933', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{V}"),("fixmath","\\mathbold{V}"),("unicode-math","\\mbfitV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119934', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{W}"),("fixmath","\\mathbold{W}"),("unicode-math","\\mbfitW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119935', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{X}"),("fixmath","\\mathbold{X}"),("unicode-math","\\mbfitX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119936', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{Y}"),("fixmath","\\mathbold{Y}"),("unicode-math","\\mbfitY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119937', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{Z}"),("fixmath","\\mathbold{Z}"),("unicode-math","\\mbfitZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119938', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{a}"),("fixmath","\\mathbold{a}"),("unicode-math","\\mbfita")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119939', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{b}"),("fixmath","\\mathbold{b}"),("unicode-math","\\mbfitb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119940', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{c}"),("fixmath","\\mathbold{c}"),("unicode-math","\\mbfitc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119941', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{d}"),("fixmath","\\mathbold{d}"),("unicode-math","\\mbfitd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119942', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{e}"),("fixmath","\\mathbold{e}"),("unicode-math","\\mbfite")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119943', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{f}"),("fixmath","\\mathbold{f}"),("unicode-math","\\mbfitf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119944', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{g}"),("fixmath","\\mathbold{g}"),("unicode-math","\\mbfitg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119945', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{h}"),("fixmath","\\mathbold{h}"),("unicode-math","\\mbfith")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119946', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{i}"),("fixmath","\\mathbold{i}"),("unicode-math","\\mbfiti")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119947', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{j}"),("fixmath","\\mathbold{j}"),("unicode-math","\\mbfitj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119948', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{k}"),("fixmath","\\mathbold{k}"),("unicode-math","\\mbfitk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119949', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{l}"),("fixmath","\\mathbold{l}"),("unicode-math","\\mbfitl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119950', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{m}"),("fixmath","\\mathbold{m}"),("unicode-math","\\mbfitm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119951', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{n}"),("fixmath","\\mathbold{n}"),("unicode-math","\\mbfitn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119952', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{o}"),("fixmath","\\mathbold{o}"),("unicode-math","\\mbfito")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119953', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{p}"),("fixmath","\\mathbold{p}"),("unicode-math","\\mbfitp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119954', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{q}"),("fixmath","\\mathbold{q}"),("unicode-math","\\mbfitq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119955', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{r}"),("fixmath","\\mathbold{r}"),("unicode-math","\\mbfitr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119956', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{s}"),("fixmath","\\mathbold{s}"),("unicode-math","\\mbfits")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119957', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{t}"),("fixmath","\\mathbold{t}"),("unicode-math","\\mbfitt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119958', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{u}"),("fixmath","\\mathbold{u}"),("unicode-math","\\mbfitu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119959', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{v}"),("fixmath","\\mathbold{v}"),("unicode-math","\\mbfitv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119960', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{w}"),("fixmath","\\mathbold{w}"),("unicode-math","\\mbfitw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119961', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{x}"),("fixmath","\\mathbold{x}"),("unicode-math","\\mbfitx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119962', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{y}"),("fixmath","\\mathbold{y}"),("unicode-math","\\mbfity")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119963', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{z}"),("fixmath","\\mathbold{z}"),("unicode-math","\\mbfitz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119964', commands :: [(Text, Text)]
commands = [("base","\\mathcal{A}"),("unicode-math","\\mscrA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119966', commands :: [(Text, Text)]
commands = [("base","\\mathcal{C}"),("unicode-math","\\mscrC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119967', commands :: [(Text, Text)]
commands = [("base","\\mathcal{D}"),("unicode-math","\\mscrD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119970', commands :: [(Text, Text)]
commands = [("base","\\mathcal{G}"),("unicode-math","\\mscrG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119973', commands :: [(Text, Text)]
commands = [("base","\\mathcal{J}"),("unicode-math","\\mscrJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119974', commands :: [(Text, Text)]
commands = [("base","\\mathcal{K}"),("unicode-math","\\mscrK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119977', commands :: [(Text, Text)]
commands = [("base","\\mathcal{N}"),("unicode-math","\\mscrN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119978', commands :: [(Text, Text)]
commands = [("base","\\mathcal{O}"),("unicode-math","\\mscrO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119979', commands :: [(Text, Text)]
commands = [("base","\\mathcal{P}"),("unicode-math","\\mscrP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119980', commands :: [(Text, Text)]
commands = [("base","\\mathcal{Q}"),("unicode-math","\\mscrQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119982', commands :: [(Text, Text)]
commands = [("base","\\mathcal{S}"),("unicode-math","\\mscrS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119983', commands :: [(Text, Text)]
commands = [("base","\\mathcal{T}"),("unicode-math","\\mscrT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119984', commands :: [(Text, Text)]
commands = [("base","\\mathcal{U}"),("unicode-math","\\mscrU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119985', commands :: [(Text, Text)]
commands = [("base","\\mathcal{V}"),("unicode-math","\\mscrV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119986', commands :: [(Text, Text)]
commands = [("base","\\mathcal{W}"),("unicode-math","\\mscrW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119987', commands :: [(Text, Text)]
commands = [("base","\\mathcal{X}"),("unicode-math","\\mscrX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119988', commands :: [(Text, Text)]
commands = [("base","\\mathcal{Y}"),("unicode-math","\\mscrY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119989', commands :: [(Text, Text)]
commands = [("base","\\mathcal{Z}"),("unicode-math","\\mscrZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119990', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{a}"),("unicode-math","\\mscra")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119991', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{b}"),("unicode-math","\\mscrb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119992', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{c}"),("unicode-math","\\mscrc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119993', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{d}"),("unicode-math","\\mscrd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119995', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{f}"),("unicode-math","\\mscrf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119997', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{h}"),("unicode-math","\\mscrh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119998', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{i}"),("unicode-math","\\mscri")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\119999', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{j}"),("unicode-math","\\mscrj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120000', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{k}"),("unicode-math","\\mscrk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120001', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{l}"),("unicode-math","\\mscrl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120002', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{m}"),("unicode-math","\\mscrm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120003', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{n}"),("unicode-math","\\mscrn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120005', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{p}"),("unicode-math","\\mscrp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120006', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{q}"),("unicode-math","\\mscrq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120007', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{r}"),("unicode-math","\\mscrr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120008', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{s}"),("unicode-math","\\mscrs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120009', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{t}"),("unicode-math","\\mscrt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120010', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{u}"),("unicode-math","\\mscru")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120011', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{v}"),("unicode-math","\\mscrv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120012', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{w}"),("unicode-math","\\mscrw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120013', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{x}"),("unicode-math","\\mscrx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120014', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{y}"),("unicode-math","\\mscry")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120015', commands :: [(Text, Text)]
commands = [("urwchancal","\\mathcal{z}"),("unicode-math","\\mscrz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SCRIPT SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120016', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120017', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120018', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120019', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120020', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120021', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120022', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120023', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120024', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120025', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120026', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120027', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120028', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120029', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120030', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120031', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120032', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120033', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120034', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120035', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120036', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120037', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120038', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120039', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120040', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120041', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120042', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscra")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120043', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120044', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120045', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120046', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscre")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120047', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120048', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120049', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120050', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscri")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120051', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120052', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120053', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120054', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120055', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120056', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscro")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120057', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120058', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120059', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120060', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120061', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120062', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscru")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120063', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120064', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120065', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120066', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscry")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120067', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfscrz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SCRIPT SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120068', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{A}"),("unicode-math","\\mfrakA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120069', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{B}"),("unicode-math","\\mfrakB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120071', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{D}"),("unicode-math","\\mfrakD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120072', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{E}"),("unicode-math","\\mfrakE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120073', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{F}"),("unicode-math","\\mfrakF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120074', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{G}"),("unicode-math","\\mfrakG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120077', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{J}"),("unicode-math","\\mfrakJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120078', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{K}"),("unicode-math","\\mfrakK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120079', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{L}"),("unicode-math","\\mfrakL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120080', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{M}"),("unicode-math","\\mfrakM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120081', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{N}"),("unicode-math","\\mfrakN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120082', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{O}"),("unicode-math","\\mfrakO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120083', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{P}"),("unicode-math","\\mfrakP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120084', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{Q}"),("unicode-math","\\mfrakQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120086', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{S}"),("unicode-math","\\mfrakS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120087', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{T}"),("unicode-math","\\mfrakT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120088', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{U}"),("unicode-math","\\mfrakU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120089', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{V}"),("unicode-math","\\mfrakV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120090', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{W}"),("unicode-math","\\mfrakW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120091', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{X}"),("unicode-math","\\mfrakX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120092', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{Y}"),("unicode-math","\\mfrakY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120094', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{a}"),("unicode-math","\\mfraka")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120095', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{b}"),("unicode-math","\\mfrakb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120096', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{c}"),("unicode-math","\\mfrakc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120097', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{d}"),("unicode-math","\\mfrakd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120098', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{e}"),("unicode-math","\\mfrake")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120099', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{f}"),("unicode-math","\\mfrakf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120100', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{g}"),("unicode-math","\\mfrakg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120101', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{h}"),("unicode-math","\\mfrakh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120102', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{i}"),("unicode-math","\\mfraki")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120103', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{j}"),("unicode-math","\\mfrakj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120104', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{k}"),("unicode-math","\\mfrakk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120105', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{l}"),("unicode-math","\\mfrakl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120106', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{m}"),("unicode-math","\\mfrakm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120107', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{n}"),("unicode-math","\\mfrakn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120108', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{o}"),("unicode-math","\\mfrako")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120109', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{p}"),("unicode-math","\\mfrakp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120110', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{q}"),("unicode-math","\\mfrakq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120111', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{r}"),("unicode-math","\\mfrakr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120112', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{s}"),("unicode-math","\\mfraks")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120113', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{t}"),("unicode-math","\\mfrakt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120114', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{u}"),("unicode-math","\\mfraku")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120115', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{v}"),("unicode-math","\\mfrakv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120116', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{w}"),("unicode-math","\\mfrakw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120117', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{x}"),("unicode-math","\\mfrakx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120118', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{y}"),("unicode-math","\\mfraky")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120119', commands :: [(Text, Text)]
commands = [("eufrak","\\mathfrak{z}"),("unicode-math","\\mfrakz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL FRAKTUR SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120120', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{A}"),("dsfont","\\mathds{A}"),("unicode-math","\\BbbA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120121', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{B}"),("dsfont","\\mathds{B}"),("unicode-math","\\BbbB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120123', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{D}"),("dsfont","\\mathds{D}"),("unicode-math","\\BbbD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120124', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{E}"),("dsfont","\\mathds{E}"),("unicode-math","\\BbbE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120125', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{F}"),("dsfont","\\mathds{F}"),("unicode-math","\\BbbF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120126', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{G}"),("dsfont","\\mathds{G}"),("unicode-math","\\BbbG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120128', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{I}"),("dsfont","\\mathds{I}"),("unicode-math","\\BbbI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120129', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{J}"),("dsfont","\\mathds{J}"),("unicode-math","\\BbbJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120130', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{K}"),("dsfont","\\mathds{K}"),("unicode-math","\\BbbK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120131', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{L}"),("dsfont","\\mathds{L}"),("unicode-math","\\BbbL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120132', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{M}"),("dsfont","\\mathds{M}"),("unicode-math","\\BbbM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120134', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{O}"),("dsfont","\\mathds{O}"),("unicode-math","\\BbbO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120138', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{S}"),("dsfont","\\mathds{S}"),("unicode-math","\\BbbS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120139', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{T}"),("dsfont","\\mathds{T}"),("unicode-math","\\BbbT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120140', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{U}"),("dsfont","\\mathds{U}"),("unicode-math","\\BbbU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120141', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{V}"),("dsfont","\\mathds{V}"),("unicode-math","\\BbbV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120142', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{W}"),("dsfont","\\mathds{W}"),("unicode-math","\\BbbW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120143', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{X}"),("dsfont","\\mathds{X}"),("unicode-math","\\BbbX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120144', commands :: [(Text, Text)]
commands = [("mathbb","\\mathbb{Y}"),("dsfont","\\mathds{Y}"),("unicode-math","\\BbbY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "matMATHEMATICAL DOUBLE-STRUCK CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120146', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{a}"),("unicode-math","\\Bbba")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120147', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{b}"),("unicode-math","\\Bbbb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120148', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{c}"),("unicode-math","\\Bbbc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120149', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{d}"),("unicode-math","\\Bbbd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120150', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{e}"),("unicode-math","\\Bbbe")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120151', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{f}"),("unicode-math","\\Bbbf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120152', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{g}"),("unicode-math","\\Bbbg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120153', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{h}"),("unicode-math","\\Bbbh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120154', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{i}"),("unicode-math","\\Bbbi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120155', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{j}"),("unicode-math","\\Bbbj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120156', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{k}"),("fourier","\\mathbb{k}"),("amssymb","\\Bbbk"),("unicode-math","\\Bbbk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120157', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{l}"),("unicode-math","\\Bbbl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120158', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{m}"),("unicode-math","\\Bbbm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120159', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{n}"),("unicode-math","\\Bbbn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120160', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{o}"),("unicode-math","\\Bbbo")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120161', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{p}"),("unicode-math","\\Bbbp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120162', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{q}"),("unicode-math","\\Bbbq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120163', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{r}"),("unicode-math","\\Bbbr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120164', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{s}"),("unicode-math","\\Bbbs")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120165', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{t}"),("unicode-math","\\Bbbt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120166', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{u}"),("unicode-math","\\Bbbu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120167', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{v}"),("unicode-math","\\Bbbv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120168', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{w}"),("unicode-math","\\Bbbw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120169', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{x}"),("unicode-math","\\Bbbx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120170', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{y}"),("unicode-math","\\Bbby")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120171', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{z}"),("unicode-math","\\Bbbz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL DOUBLE-STRUCK SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120172', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120173', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120174', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120175', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120176', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120177', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120178', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120179', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120180', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120181', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120182', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120183', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120184', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120185', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120186', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120187', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120188', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120189', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120190', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120191', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120192', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120193', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120194', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120195', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120196', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120197', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120198', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffraka")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120199', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120200', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120201', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120202', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrake")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120203', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120204', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120205', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120206', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffraki")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120207', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120208', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120209', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120210', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120211', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120212', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrako")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120213', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120214', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120215', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120216', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffraks")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120217', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120218', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffraku")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120219', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120220', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120221', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120222', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffraky")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120223', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbffrakz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD FRAKTUR SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120224', commands :: [(Text, Text)]
commands = [("base","\\mathsf{A}"),("unicode-math","\\msansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120225', commands :: [(Text, Text)]
commands = [("base","\\mathsf{B}"),("unicode-math","\\msansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120226', commands :: [(Text, Text)]
commands = [("base","\\mathsf{C}"),("unicode-math","\\msansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120227', commands :: [(Text, Text)]
commands = [("base","\\mathsf{D}"),("unicode-math","\\msansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120228', commands :: [(Text, Text)]
commands = [("base","\\mathsf{E}"),("unicode-math","\\msansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120229', commands :: [(Text, Text)]
commands = [("base","\\mathsf{F}"),("unicode-math","\\msansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120230', commands :: [(Text, Text)]
commands = [("base","\\mathsf{G}"),("unicode-math","\\msansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120231', commands :: [(Text, Text)]
commands = [("base","\\mathsf{H}"),("unicode-math","\\msansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120232', commands :: [(Text, Text)]
commands = [("base","\\mathsf{I}"),("unicode-math","\\msansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120233', commands :: [(Text, Text)]
commands = [("base","\\mathsf{J}"),("unicode-math","\\msansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120234', commands :: [(Text, Text)]
commands = [("base","\\mathsf{K}"),("unicode-math","\\msansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120235', commands :: [(Text, Text)]
commands = [("base","\\mathsf{L}"),("unicode-math","\\msansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120236', commands :: [(Text, Text)]
commands = [("base","\\mathsf{M}"),("unicode-math","\\msansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120237', commands :: [(Text, Text)]
commands = [("base","\\mathsf{N}"),("unicode-math","\\msansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120238', commands :: [(Text, Text)]
commands = [("base","\\mathsf{O}"),("unicode-math","\\msansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120239', commands :: [(Text, Text)]
commands = [("base","\\mathsf{P}"),("unicode-math","\\msansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120240', commands :: [(Text, Text)]
commands = [("base","\\mathsf{Q}"),("unicode-math","\\msansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120241', commands :: [(Text, Text)]
commands = [("base","\\mathsf{R}"),("unicode-math","\\msansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120242', commands :: [(Text, Text)]
commands = [("base","\\mathsf{S}"),("unicode-math","\\msansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120243', commands :: [(Text, Text)]
commands = [("base","\\mathsf{T}"),("unicode-math","\\msansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120244', commands :: [(Text, Text)]
commands = [("base","\\mathsf{U}"),("unicode-math","\\msansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120245', commands :: [(Text, Text)]
commands = [("base","\\mathsf{V}"),("unicode-math","\\msansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120246', commands :: [(Text, Text)]
commands = [("base","\\mathsf{W}"),("unicode-math","\\msansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120247', commands :: [(Text, Text)]
commands = [("base","\\mathsf{X}"),("unicode-math","\\msansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120248', commands :: [(Text, Text)]
commands = [("base","\\mathsf{Y}"),("unicode-math","\\msansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120249', commands :: [(Text, Text)]
commands = [("base","\\mathsf{Z}"),("unicode-math","\\msansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120250', commands :: [(Text, Text)]
commands = [("base","\\mathsf{a}"),("unicode-math","\\msansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120251', commands :: [(Text, Text)]
commands = [("base","\\mathsf{b}"),("unicode-math","\\msansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120252', commands :: [(Text, Text)]
commands = [("base","\\mathsf{c}"),("unicode-math","\\msansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120253', commands :: [(Text, Text)]
commands = [("base","\\mathsf{d}"),("unicode-math","\\msansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120254', commands :: [(Text, Text)]
commands = [("base","\\mathsf{e}"),("unicode-math","\\msanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120255', commands :: [(Text, Text)]
commands = [("base","\\mathsf{f}"),("unicode-math","\\msansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120256', commands :: [(Text, Text)]
commands = [("base","\\mathsf{g}"),("unicode-math","\\msansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120257', commands :: [(Text, Text)]
commands = [("base","\\mathsf{h}"),("unicode-math","\\msansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120258', commands :: [(Text, Text)]
commands = [("base","\\mathsf{i}"),("unicode-math","\\msansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120259', commands :: [(Text, Text)]
commands = [("base","\\mathsf{j}"),("unicode-math","\\msansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120260', commands :: [(Text, Text)]
commands = [("base","\\mathsf{k}"),("unicode-math","\\msansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120261', commands :: [(Text, Text)]
commands = [("base","\\mathsf{l}"),("unicode-math","\\msansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120262', commands :: [(Text, Text)]
commands = [("base","\\mathsf{m}"),("unicode-math","\\msansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120263', commands :: [(Text, Text)]
commands = [("base","\\mathsf{n}"),("unicode-math","\\msansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120264', commands :: [(Text, Text)]
commands = [("base","\\mathsf{o}"),("unicode-math","\\msanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120265', commands :: [(Text, Text)]
commands = [("base","\\mathsf{p}"),("unicode-math","\\msansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120266', commands :: [(Text, Text)]
commands = [("base","\\mathsf{q}"),("unicode-math","\\msansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120267', commands :: [(Text, Text)]
commands = [("base","\\mathsf{r}"),("unicode-math","\\msansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120268', commands :: [(Text, Text)]
commands = [("base","\\mathsf{s}"),("unicode-math","\\msanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120269', commands :: [(Text, Text)]
commands = [("base","\\mathsf{t}"),("unicode-math","\\msanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120270', commands :: [(Text, Text)]
commands = [("base","\\mathsf{u}"),("unicode-math","\\msansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120271', commands :: [(Text, Text)]
commands = [("base","\\mathsf{v}"),("unicode-math","\\msansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120272', commands :: [(Text, Text)]
commands = [("base","\\mathsf{w}"),("unicode-math","\\msansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120273', commands :: [(Text, Text)]
commands = [("base","\\mathsf{x}"),("unicode-math","\\msansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120274', commands :: [(Text, Text)]
commands = [("base","\\mathsf{y}"),("unicode-math","\\msansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120275', commands :: [(Text, Text)]
commands = [("base","\\mathsf{z}"),("unicode-math","\\msansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120276', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{A}"),("unicode-math","\\mbfsansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120277', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{B}"),("unicode-math","\\mbfsansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120278', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{C}"),("unicode-math","\\mbfsansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120279', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{D}"),("unicode-math","\\mbfsansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120280', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{E}"),("unicode-math","\\mbfsansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120281', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{F}"),("unicode-math","\\mbfsansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120282', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{G}"),("unicode-math","\\mbfsansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120283', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{H}"),("unicode-math","\\mbfsansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120284', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{I}"),("unicode-math","\\mbfsansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120285', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{J}"),("unicode-math","\\mbfsansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120286', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{K}"),("unicode-math","\\mbfsansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120287', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{L}"),("unicode-math","\\mbfsansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120288', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{M}"),("unicode-math","\\mbfsansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120289', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{N}"),("unicode-math","\\mbfsansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120290', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{O}"),("unicode-math","\\mbfsansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120291', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{P}"),("unicode-math","\\mbfsansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120292', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{Q}"),("unicode-math","\\mbfsansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120293', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{R}"),("unicode-math","\\mbfsansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120294', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{S}"),("unicode-math","\\mbfsansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120295', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{T}"),("unicode-math","\\mbfsansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120296', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{U}"),("unicode-math","\\mbfsansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120297', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{V}"),("unicode-math","\\mbfsansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120298', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{W}"),("unicode-math","\\mbfsansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120299', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{X}"),("unicode-math","\\mbfsansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120300', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{Y}"),("unicode-math","\\mbfsansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120301', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{Z}"),("unicode-math","\\mbfsansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120302', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{a}"),("unicode-math","\\mbfsansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120303', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{b}"),("unicode-math","\\mbfsansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120304', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{c}"),("unicode-math","\\mbfsansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120305', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{d}"),("unicode-math","\\mbfsansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120306', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{e}"),("unicode-math","\\mbfsanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120307', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{f}"),("unicode-math","\\mbfsansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120308', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{g}"),("unicode-math","\\mbfsansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120309', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{h}"),("unicode-math","\\mbfsansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120310', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{i}"),("unicode-math","\\mbfsansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120311', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{j}"),("unicode-math","\\mbfsansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120312', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{k}"),("unicode-math","\\mbfsansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120313', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{l}"),("unicode-math","\\mbfsansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120314', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{m}"),("unicode-math","\\mbfsansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120315', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{n}"),("unicode-math","\\mbfsansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120316', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{o}"),("unicode-math","\\mbfsanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120317', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{p}"),("unicode-math","\\mbfsansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120318', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{q}"),("unicode-math","\\mbfsansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120319', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{r}"),("unicode-math","\\mbfsansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120320', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{s}"),("unicode-math","\\mbfsanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120321', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{t}"),("unicode-math","\\mbfsanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120322', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{u}"),("unicode-math","\\mbfsansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120323', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{v}"),("unicode-math","\\mbfsansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120324', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{w}"),("unicode-math","\\mbfsansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120325', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{x}"),("unicode-math","\\mbfsansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120326', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{y}"),("unicode-math","\\mbfsansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120327', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{z}"),("unicode-math","\\mbfsansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120328', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{A}"),("unicode-math","\\mitsansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120329', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{B}"),("unicode-math","\\mitsansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120330', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{C}"),("unicode-math","\\mitsansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120331', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{D}"),("unicode-math","\\mitsansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120332', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{E}"),("unicode-math","\\mitsansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120333', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{F}"),("unicode-math","\\mitsansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120334', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{G}"),("unicode-math","\\mitsansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120335', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{H}"),("unicode-math","\\mitsansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120336', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{I}"),("unicode-math","\\mitsansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120337', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{J}"),("unicode-math","\\mitsansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120338', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{K}"),("unicode-math","\\mitsansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120339', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{L}"),("unicode-math","\\mitsansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120340', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{M}"),("unicode-math","\\mitsansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120341', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{N}"),("unicode-math","\\mitsansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120342', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{O}"),("unicode-math","\\mitsansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120343', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{P}"),("unicode-math","\\mitsansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120344', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{Q}"),("unicode-math","\\mitsansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120345', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{R}"),("unicode-math","\\mitsansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120346', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{S}"),("unicode-math","\\mitsansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120347', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{T}"),("unicode-math","\\mitsansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120348', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{U}"),("unicode-math","\\mitsansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120349', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{V}"),("unicode-math","\\mitsansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120350', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{W}"),("unicode-math","\\mitsansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120351', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{X}"),("unicode-math","\\mitsansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120352', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{Y}"),("unicode-math","\\mitsansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120353', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{Z}"),("unicode-math","\\mitsansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120354', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{a}"),("unicode-math","\\mitsansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120355', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{b}"),("unicode-math","\\mitsansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120356', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{c}"),("unicode-math","\\mitsansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120357', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{d}"),("unicode-math","\\mitsansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120358', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{e}"),("unicode-math","\\mitsanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120359', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{f}"),("unicode-math","\\mitsansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120360', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{g}"),("unicode-math","\\mitsansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120361', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{h}"),("unicode-math","\\mitsansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120362', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{i}"),("unicode-math","\\mitsansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120363', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{j}"),("unicode-math","\\mitsansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120364', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{k}"),("unicode-math","\\mitsansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120365', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{l}"),("unicode-math","\\mitsansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120366', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{m}"),("unicode-math","\\mitsansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120367', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{n}"),("unicode-math","\\mitsansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120368', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{o}"),("unicode-math","\\mitsanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120369', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{p}"),("unicode-math","\\mitsansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120370', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{q}"),("unicode-math","\\mitsansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120371', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{r}"),("unicode-math","\\mitsansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120372', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{s}"),("unicode-math","\\mitsanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120373', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{t}"),("unicode-math","\\mitsanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120374', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{u}"),("unicode-math","\\mitsansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120375', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{v}"),("unicode-math","\\mitsansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120376', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{w}"),("unicode-math","\\mitsansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120377', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{x}"),("unicode-math","\\mitsansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120378', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{y}"),("unicode-math","\\mitsansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120379', commands :: [(Text, Text)]
commands = [("omlmathsfit","\\mathsfit{z}"),("unicode-math","\\mitsansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF ITALIC SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120380', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{A}"),("unicode-math","\\mbfitsansA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120381', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{B}"),("unicode-math","\\mbfitsansB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120382', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{C}"),("unicode-math","\\mbfitsansC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120383', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{D}"),("unicode-math","\\mbfitsansD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120384', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{E}"),("unicode-math","\\mbfitsansE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120385', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{F}"),("unicode-math","\\mbfitsansF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120386', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{G}"),("unicode-math","\\mbfitsansG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120387', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{H}"),("unicode-math","\\mbfitsansH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120388', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{I}"),("unicode-math","\\mbfitsansI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120389', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{J}"),("unicode-math","\\mbfitsansJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120390', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{K}"),("unicode-math","\\mbfitsansK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120391', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{L}"),("unicode-math","\\mbfitsansL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120392', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{M}"),("unicode-math","\\mbfitsansM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120393', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{N}"),("unicode-math","\\mbfitsansN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120394', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{O}"),("unicode-math","\\mbfitsansO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120395', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{P}"),("unicode-math","\\mbfitsansP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120396', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{Q}"),("unicode-math","\\mbfitsansQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120397', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{R}"),("unicode-math","\\mbfitsansR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120398', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{S}"),("unicode-math","\\mbfitsansS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120399', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{T}"),("unicode-math","\\mbfitsansT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120400', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{U}"),("unicode-math","\\mbfitsansU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120401', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{V}"),("unicode-math","\\mbfitsansV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120402', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{W}"),("unicode-math","\\mbfitsansW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120403', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{X}"),("unicode-math","\\mbfitsansX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120404', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{Y}"),("unicode-math","\\mbfitsansY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120405', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{Z}"),("unicode-math","\\mbfitsansZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120406', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{a}"),("unicode-math","\\mbfitsansa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120407', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{b}"),("unicode-math","\\mbfitsansb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120408', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{c}"),("unicode-math","\\mbfitsansc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120409', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{d}"),("unicode-math","\\mbfitsansd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120410', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{e}"),("unicode-math","\\mbfitsanse")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120411', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{f}"),("unicode-math","\\mbfitsansf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120412', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{g}"),("unicode-math","\\mbfitsansg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120413', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{h}"),("unicode-math","\\mbfitsansh")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120414', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{i}"),("unicode-math","\\mbfitsansi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120415', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{j}"),("unicode-math","\\mbfitsansj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120416', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{k}"),("unicode-math","\\mbfitsansk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120417', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{l}"),("unicode-math","\\mbfitsansl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120418', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{m}"),("unicode-math","\\mbfitsansm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120419', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{n}"),("unicode-math","\\mbfitsansn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120420', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{o}"),("unicode-math","\\mbfitsanso")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120421', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{p}"),("unicode-math","\\mbfitsansp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120422', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{q}"),("unicode-math","\\mbfitsansq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120423', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{r}"),("unicode-math","\\mbfitsansr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120424', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{s}"),("unicode-math","\\mbfitsanss")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120425', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{t}"),("unicode-math","\\mbfitsanst")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120426', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{u}"),("unicode-math","\\mbfitsansu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120427', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{v}"),("unicode-math","\\mbfitsansv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120428', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{w}"),("unicode-math","\\mbfitsansw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120429', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{x}"),("unicode-math","\\mbfitsansx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120430', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{y}"),("unicode-math","\\mbfitsansy")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120431', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{z}"),("unicode-math","\\mbfitsansz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120432', commands :: [(Text, Text)]
commands = [("base","\\mathtt{A}"),("unicode-math","\\mttA")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120433', commands :: [(Text, Text)]
commands = [("base","\\mathtt{B}"),("unicode-math","\\mttB")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120434', commands :: [(Text, Text)]
commands = [("base","\\mathtt{C}"),("unicode-math","\\mttC")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120435', commands :: [(Text, Text)]
commands = [("base","\\mathtt{D}"),("unicode-math","\\mttD")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120436', commands :: [(Text, Text)]
commands = [("base","\\mathtt{E}"),("unicode-math","\\mttE")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120437', commands :: [(Text, Text)]
commands = [("base","\\mathtt{F}"),("unicode-math","\\mttF")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120438', commands :: [(Text, Text)]
commands = [("base","\\mathtt{G}"),("unicode-math","\\mttG")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120439', commands :: [(Text, Text)]
commands = [("base","\\mathtt{H}"),("unicode-math","\\mttH")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120440', commands :: [(Text, Text)]
commands = [("base","\\mathtt{I}"),("unicode-math","\\mttI")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120441', commands :: [(Text, Text)]
commands = [("base","\\mathtt{J}"),("unicode-math","\\mttJ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120442', commands :: [(Text, Text)]
commands = [("base","\\mathtt{K}"),("unicode-math","\\mttK")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120443', commands :: [(Text, Text)]
commands = [("base","\\mathtt{L}"),("unicode-math","\\mttL")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120444', commands :: [(Text, Text)]
commands = [("base","\\mathtt{M}"),("unicode-math","\\mttM")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120445', commands :: [(Text, Text)]
commands = [("base","\\mathtt{N}"),("unicode-math","\\mttN")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120446', commands :: [(Text, Text)]
commands = [("base","\\mathtt{O}"),("unicode-math","\\mttO")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120447', commands :: [(Text, Text)]
commands = [("base","\\mathtt{P}"),("unicode-math","\\mttP")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120448', commands :: [(Text, Text)]
commands = [("base","\\mathtt{Q}"),("unicode-math","\\mttQ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120449', commands :: [(Text, Text)]
commands = [("base","\\mathtt{R}"),("unicode-math","\\mttR")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120450', commands :: [(Text, Text)]
commands = [("base","\\mathtt{S}"),("unicode-math","\\mttS")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120451', commands :: [(Text, Text)]
commands = [("base","\\mathtt{T}"),("unicode-math","\\mttT")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120452', commands :: [(Text, Text)]
commands = [("base","\\mathtt{U}"),("unicode-math","\\mttU")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120453', commands :: [(Text, Text)]
commands = [("base","\\mathtt{V}"),("unicode-math","\\mttV")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120454', commands :: [(Text, Text)]
commands = [("base","\\mathtt{W}"),("unicode-math","\\mttW")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120455', commands :: [(Text, Text)]
commands = [("base","\\mathtt{X}"),("unicode-math","\\mttX")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120456', commands :: [(Text, Text)]
commands = [("base","\\mathtt{Y}"),("unicode-math","\\mttY")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120457', commands :: [(Text, Text)]
commands = [("base","\\mathtt{Z}"),("unicode-math","\\mttZ")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE CAPITAL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120458', commands :: [(Text, Text)]
commands = [("base","\\mathtt{a}"),("unicode-math","\\mtta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL A"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120459', commands :: [(Text, Text)]
commands = [("base","\\mathtt{b}"),("unicode-math","\\mttb")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL B"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120460', commands :: [(Text, Text)]
commands = [("base","\\mathtt{c}"),("unicode-math","\\mttc")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL C"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120461', commands :: [(Text, Text)]
commands = [("base","\\mathtt{d}"),("unicode-math","\\mttd")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL D"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120462', commands :: [(Text, Text)]
commands = [("base","\\mathtt{e}"),("unicode-math","\\mtte")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL E"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120463', commands :: [(Text, Text)]
commands = [("base","\\mathtt{f}"),("unicode-math","\\mttf")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL F"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120464', commands :: [(Text, Text)]
commands = [("base","\\mathtt{g}"),("unicode-math","\\mttg")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL G"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120465', commands :: [(Text, Text)]
commands = [("base","\\mathtt{h}"),("unicode-math","\\mtth")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL H"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120466', commands :: [(Text, Text)]
commands = [("base","\\mathtt{i}"),("unicode-math","\\mtti")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120467', commands :: [(Text, Text)]
commands = [("base","\\mathtt{j}"),("unicode-math","\\mttj")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120468', commands :: [(Text, Text)]
commands = [("base","\\mathtt{k}"),("unicode-math","\\mttk")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL K"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120469', commands :: [(Text, Text)]
commands = [("base","\\mathtt{l}"),("unicode-math","\\mttl")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL L"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120470', commands :: [(Text, Text)]
commands = [("base","\\mathtt{m}"),("unicode-math","\\mttm")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL M"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120471', commands :: [(Text, Text)]
commands = [("base","\\mathtt{n}"),("unicode-math","\\mttn")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL N"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120472', commands :: [(Text, Text)]
commands = [("base","\\mathtt{o}"),("unicode-math","\\mtto")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL O"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120473', commands :: [(Text, Text)]
commands = [("base","\\mathtt{p}"),("unicode-math","\\mttp")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL P"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120474', commands :: [(Text, Text)]
commands = [("base","\\mathtt{q}"),("unicode-math","\\mttq")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL Q"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120475', commands :: [(Text, Text)]
commands = [("base","\\mathtt{r}"),("unicode-math","\\mttr")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL R"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120476', commands :: [(Text, Text)]
commands = [("base","\\mathtt{s}"),("unicode-math","\\mtts")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL S"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120477', commands :: [(Text, Text)]
commands = [("base","\\mathtt{t}"),("unicode-math","\\mttt")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL T"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120478', commands :: [(Text, Text)]
commands = [("base","\\mathtt{u}"),("unicode-math","\\mttu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL U"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120479', commands :: [(Text, Text)]
commands = [("base","\\mathtt{v}"),("unicode-math","\\mttv")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL V"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120480', commands :: [(Text, Text)]
commands = [("base","\\mathtt{w}"),("unicode-math","\\mttw")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL W"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120481', commands :: [(Text, Text)]
commands = [("base","\\mathtt{x}"),("unicode-math","\\mttx")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL X"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120482', commands :: [(Text, Text)]
commands = [("base","\\mathtt{y}"),("unicode-math","\\mtty")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL Y"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120483', commands :: [(Text, Text)]
commands = [("base","\\mathtt{z}"),("unicode-math","\\mttz")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL MONOSPACE SMALL Z"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120484', commands :: [(Text, Text)]
commands = [("base","\\imath"),("unicode-math","\\imath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL DOTLESS I"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120485', commands :: [(Text, Text)]
commands = [("base","\\jmath"),("unicode-math","\\jmath")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL DOTLESS J"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120488', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120489', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120490', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Gamma}"),("unicode-math","\\mbfGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120491', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Delta}"),("unicode-math","\\mbfDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120492', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120493', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120494', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120495', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Theta}"),("unicode-math","\\mbfTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120496', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120497', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120498', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Lambda}"),("unicode-math","\\mbfLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical bold capital lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120499', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120500', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120501', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Xi}"),("unicode-math","\\mbfXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120502', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120503', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Pi}"),("unicode-math","\\mbfPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120504', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120505', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120506', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Sigma}"),("unicode-math","\\mbfSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120507', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120508', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Upsilon}"),("unicode-math","\\mbfUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120509', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Phi}"),("unicode-math","\\mbfPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120510', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120511', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Psi}"),("unicode-math","\\mbfPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120512', commands :: [(Text, Text)]
commands = [("base","\\mathbf{\\Omega}"),("unicode-math","\\mbfOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120513', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL BOLD NABLA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120514', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\alpha}"),("unicode-math","\\mbfalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120515', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\beta}"),("unicode-math","\\mbfbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120516', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\gamma}"),("unicode-math","\\mbfgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120517', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\delta}"),("unicode-math","\\mbfdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120518', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\varepsilon}"),("unicode-math","\\mbfepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120519', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\zeta}"),("unicode-math","\\mbfzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120520', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\eta}"),("unicode-math","\\mbfeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120521', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\theta}"),("unicode-math","\\mbftheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120522', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\iota}"),("unicode-math","\\mbfiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120523', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\kappa}"),("unicode-math","\\mbfkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120524', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\lambda}"),("unicode-math","\\mbflambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical bold small lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120525', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\mu}"),("unicode-math","\\mbfmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120526', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\nu}"),("unicode-math","\\mbfnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120527', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\xi}"),("unicode-math","\\mbfxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120528', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120529', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\pi}"),("unicode-math","\\mbfpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120530', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\rho}"),("unicode-math","\\mbfrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120531', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\varsigma}"),("unicode-math","\\mbfvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL FINAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120532', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\sigma}"),("unicode-math","\\mbfsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120533', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\tau}"),("unicode-math","\\mbftau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120534', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\upsilon}"),("unicode-math","\\mbfupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120535', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\varphi}"),("unicode-math","\\mbfvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120536', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\chi}"),("unicode-math","\\mbfchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120537', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\psi}"),("unicode-math","\\mbfpsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120538', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\omega}"),("unicode-math","\\mbfomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120539', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfpartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL BOLD PARTIAL DIFFERENTIAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120540', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\epsilon}"),("unicode-math","\\mbfvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD EPSILON SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120541', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\vartheta}"),("unicode-math","\\mbfvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120542', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD KAPPA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120543', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\phi}"),("unicode-math","\\mbfphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD PHI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120544', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\varrho}"),("unicode-math","\\mbfvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD RHO SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120545', commands :: [(Text, Text)]
commands = [("omlmathbf","\\mathbf{\\varpi}"),("unicode-math","\\mbfvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD PI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120546', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120547', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120548', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Gamma"),("-fourier","\\mathit{\\Gamma}"),("unicode-math","\\mitGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varGamma (amsmath fourier), MATHEMATICAL ITALIC CAPITAL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120549', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Delta"),("-fourier","\\mathit{\\Delta}"),("unicode-math","\\mitDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varDelta (amsmath fourier), MATHEMATICAL ITALIC CAPITAL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120550', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120551', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120552', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120553', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Theta"),("-fourier","\\mathit{\\Theta}"),("unicode-math","\\mitTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varTheta (amsmath fourier), MATHEMATICAL ITALIC CAPITAL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120554', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120555', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120556', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Lambda"),("-fourier","\\mathit{\\Lambda}"),("unicode-math","\\mitLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varLambda (amsmath fourier), mathematical italic capital lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120557', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120558', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120559', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Xi"),("-fourier","\\mathit{\\Xi}"),("unicode-math","\\mitXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varXi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120560', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120561', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Pi"),("-fourier","\\mathit{\\Pi}"),("unicode-math","\\mitPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varPi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120562', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120563', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120564', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Sigma"),("-fourier","\\mathit{\\Sigma}"),("unicode-math","\\mitSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varSigma (amsmath fourier), MATHEMATICAL ITALIC CAPITAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120565', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120566', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Upsilon"),("-fourier","\\mathit{\\Upsilon}"),("unicode-math","\\mitUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varUpsilon (amsmath fourier), MATHEMATICAL ITALIC CAPITAL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120567', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Phi"),("-fourier","\\mathit{\\Phi}"),("unicode-math","\\mitPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varPhi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120568', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC CAPITAL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120569', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Psi"),("-fourier","\\mathit{\\Psi}"),("unicode-math","\\mitPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varPsi (amsmath fourier), MATHEMATICAL ITALIC CAPITAL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120570', commands :: [(Text, Text)]
commands = [("slantedGreek","\\Omega"),("-fourier","\\mathit{\\Omega}"),("unicode-math","\\mitOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "= \\varOmega (amsmath fourier), MATHEMATICAL ITALIC CAPITAL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120571', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL ITALIC NABLA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120572', commands :: [(Text, Text)]
commands = [("base","\\alpha"),("omlmathit","\\mathit{\\alpha}"),("unicode-math","\\mitalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120573', commands :: [(Text, Text)]
commands = [("base","\\beta"),("omlmathit","\\mathit{\\beta}"),("unicode-math","\\mitbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120574', commands :: [(Text, Text)]
commands = [("base","\\gamma"),("omlmathit","\\mathit{\\gamma}"),("unicode-math","\\mitgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120575', commands :: [(Text, Text)]
commands = [("base","\\delta"),("omlmathit","\\mathit{\\delta}"),("unicode-math","\\mitdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120576', commands :: [(Text, Text)]
commands = [("base","\\varepsilon"),("omlmathit","\\mathit{\\varepsilon}"),("unicode-math","\\mitepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120577', commands :: [(Text, Text)]
commands = [("base","\\zeta"),("omlmathit","\\mathit{\\zeta}"),("unicode-math","\\mitzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120578', commands :: [(Text, Text)]
commands = [("base","\\eta"),("omlmathit","\\mathit{\\eta}"),("unicode-math","\\miteta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120579', commands :: [(Text, Text)]
commands = [("base","\\theta"),("omlmathit","\\mathit{\\theta}"),("unicode-math","\\mittheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120580', commands :: [(Text, Text)]
commands = [("base","\\iota"),("omlmathit","\\mathit{\\iota}"),("unicode-math","\\mitiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120581', commands :: [(Text, Text)]
commands = [("base","\\kappa"),("omlmathit","\\mathit{\\kappa}"),("unicode-math","\\mitkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120582', commands :: [(Text, Text)]
commands = [("base","\\lambda"),("omlmathit","\\mathit{\\lambda}"),("unicode-math","\\mitlambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical italic small lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120583', commands :: [(Text, Text)]
commands = [("base","\\mu"),("omlmathit","\\mathit{\\mu}"),("unicode-math","\\mitmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120584', commands :: [(Text, Text)]
commands = [("base","\\nu"),("omlmathit","\\mathit{\\nu}"),("unicode-math","\\mitnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120585', commands :: [(Text, Text)]
commands = [("base","\\xi"),("omlmathit","\\mathit{\\xi}"),("unicode-math","\\mitxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120586', commands :: [(Text, Text)]
commands = [("unicode-math","\\mitomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120587', commands :: [(Text, Text)]
commands = [("base","\\pi"),("omlmathit","\\mathit{\\pi}"),("unicode-math","\\mitpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120588', commands :: [(Text, Text)]
commands = [("base","\\rho"),("omlmathit","\\mathit{\\rho}"),("unicode-math","\\mitrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120589', commands :: [(Text, Text)]
commands = [("base","\\varsigma"),("omlmathit","\\mathit{\\varsigma}"),("unicode-math","\\mitvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL FINAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120590', commands :: [(Text, Text)]
commands = [("base","\\sigma"),("omlmathit","\\mathit{\\sigma}"),("unicode-math","\\mitsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120591', commands :: [(Text, Text)]
commands = [("base","\\tau"),("omlmathit","\\mathit{\\tau}"),("unicode-math","\\mittau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120592', commands :: [(Text, Text)]
commands = [("base","\\upsilon"),("omlmathit","\\mathit{\\upsilon}"),("unicode-math","\\mitupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120593', commands :: [(Text, Text)]
commands = [("base","\\varphi"),("omlmathit","\\mathit{\\varphi}"),("unicode-math","\\mitphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120594', commands :: [(Text, Text)]
commands = [("base","\\chi"),("omlmathit","\\mathit{\\chi}"),("unicode-math","\\mitchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120595', commands :: [(Text, Text)]
commands = [("base","\\psi"),("omlmathit","\\mathit{\\psi}"),("unicode-math","\\mitpsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120596', commands :: [(Text, Text)]
commands = [("base","\\omega"),("omlmathit","\\mathit{\\omega}"),("unicode-math","\\mitomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC SMALL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120597', commands :: [(Text, Text)]
commands = [("base","\\partial"),("omlmathit","\\mathit{\\partial}"),("unicode-math","\\mitpartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL ITALIC PARTIAL DIFFERENTIAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120598', commands :: [(Text, Text)]
commands = [("base","\\epsilon"),("omlmathit","\\mathit{\\epsilon}"),("unicode-math","\\mitvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC EPSILON SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120599', commands :: [(Text, Text)]
commands = [("base","\\vartheta"),("omlmathit","\\mathit{\\vartheta}"),("unicode-math","\\mitvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120600', commands :: [(Text, Text)]
commands = [("amssymb","\\varkappa"),("unicode-math","\\mitvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC KAPPA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120601', commands :: [(Text, Text)]
commands = [("base","\\phi"),("omlmathit","\\mathit{\\phi}"),("unicode-math","\\mitvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC PHI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120602', commands :: [(Text, Text)]
commands = [("base","\\varrho"),("omlmathit","\\mathit{\\varrho}"),("unicode-math","\\mitvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC RHO SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120603', commands :: [(Text, Text)]
commands = [("base","\\varpi"),("omlmathit","\\mathit{\\varpi}"),("unicode-math","\\mitvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL ITALIC PI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120604', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120605', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120606', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Gamma}"),("fixmath","\\mathbold{\\Gamma}"),("unicode-math","\\mbfitGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120607', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Delta}"),("fixmath","\\mathbold{\\Delta}"),("unicode-math","\\mbfitDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120608', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120609', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120610', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120611', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Theta}"),("fixmath","\\mathbold{\\Theta}"),("unicode-math","\\mbfitTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120612', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120613', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120614', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Lambda}"),("fixmath","\\mathbold{\\Lambda}"),("unicode-math","\\mbfitLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical bold italic capital lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120615', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120616', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120617', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Xi}"),("fixmath","\\mathbold{\\Xi}"),("unicode-math","\\mbfitXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120618', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120619', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Pi}"),("fixmath","\\mathbold{\\Pi}"),("unicode-math","\\mbfitPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120620', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120621', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120622', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Sigma}"),("fixmath","\\mathbold{\\Sigma}"),("unicode-math","\\mbfitSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120623', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120624', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Upsilon}"),("fixmath","\\mathbold{\\Upsilon}"),("unicode-math","\\mbfitUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120625', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Phi}"),("fixmath","\\mathbold{\\Phi}"),("unicode-math","\\mbfitPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120626', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120627', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Psi}"),("fixmath","\\mathbold{\\Psi}"),("unicode-math","\\mbfitPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120628', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\Omega}"),("fixmath","\\mathbold{\\Omega}"),("unicode-math","\\mbfitOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC CAPITAL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120629', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC NABLA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120630', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\alpha}"),("fixmath","\\mathbold{\\alpha}"),("unicode-math","\\mbfitalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120631', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\beta}"),("fixmath","\\mathbold{\\beta}"),("unicode-math","\\mbfitbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120632', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\gamma}"),("fixmath","\\mathbold{\\gamma}"),("unicode-math","\\mbfitgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120633', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\delta}"),("fixmath","\\mathbold{\\delta}"),("unicode-math","\\mbfitdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120634', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\varepsilon}"),("fixmath","\\mathbold{\\varepsilon}"),("unicode-math","\\mbfitepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120635', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\zeta}"),("fixmath","\\mathbold{\\zeta}"),("unicode-math","\\mbfitzeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120636', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\eta}"),("fixmath","\\mathbold{\\eta}"),("unicode-math","\\mbfiteta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120637', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\theta}"),("fixmath","\\mathbold{\\theta}"),("unicode-math","\\mbfittheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120638', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\iota}"),("fixmath","\\mathbold{\\iota}"),("unicode-math","\\mbfitiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120639', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\kappa}"),("fixmath","\\mathbold{\\kappa}"),("unicode-math","\\mbfitkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120640', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\lambda}"),("fixmath","\\mathbold{\\lambda}"),("unicode-math","\\mbfitlambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical bold italic small lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120641', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\mu}"),("fixmath","\\mathbold{\\mu}"),("unicode-math","\\mbfitmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120642', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\nu}"),("fixmath","\\mathbold{\\nu}"),("unicode-math","\\mbfitnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120643', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\xi}"),("fixmath","\\mathbold{\\xi}"),("unicode-math","\\mbfitxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120644', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120645', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\pi}"),("fixmath","\\mathbold{\\pi}"),("unicode-math","\\mbfitpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120646', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\rho}"),("fixmath","\\mathbold{\\rho}"),("unicode-math","\\mbfitrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120647', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\varsigma}"),("fixmath","\\mathbold{\\varsigma}"),("unicode-math","\\mbfitvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL FINAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120648', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\sigma}"),("fixmath","\\mathbold{\\sigma}"),("unicode-math","\\mbfitsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120649', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\tau}"),("fixmath","\\mathbold{\\tau}"),("unicode-math","\\mbfittau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120650', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\upsilon}"),("fixmath","\\mathbold{\\upsilon}"),("unicode-math","\\mbfitupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120651', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\varphi}"),("fixmath","\\mathbold{\\varphi}"),("unicode-math","\\mbfitphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120652', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\chi}"),("fixmath","\\mathbold{\\chi}"),("unicode-math","\\mbfitchi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120653', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\psi}"),("fixmath","\\mathbold{\\psi}"),("unicode-math","\\mbfitpsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120654', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\omega}"),("fixmath","\\mathbold{\\omega}"),("unicode-math","\\mbfitomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC SMALL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120655', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitpartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC PARTIAL DIFFERENTIAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120656', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\epsilon}"),("fixmath","\\mathbold{\\epsilon}"),("unicode-math","\\mbfitvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC EPSILON SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120657', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\vartheta}"),("fixmath","\\mathbold{\\vartheta}"),("unicode-math","\\mbfitvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120658', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC KAPPA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120659', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\phi}"),("fixmath","\\mathbold{\\phi}"),("unicode-math","\\mbfitvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC PHI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120660', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\varrho}"),("fixmath","\\mathbold{\\varrho}"),("unicode-math","\\mbfitvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC RHO SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120661', commands :: [(Text, Text)]
commands = [("isomath","\\mathbfit{\\varpi}"),("fixmath","\\mathbold{\\varpi}"),("unicode-math","\\mbfitvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD ITALIC PI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120662', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120663', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120664', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Gamma}"),("unicode-math","\\mbfsansGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120665', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Delta}"),("unicode-math","\\mbfsansDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120666', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120667', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120668', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120669', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Theta}"),("unicode-math","\\mbfsansTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120670', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120671', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120672', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Lambda}"),("unicode-math","\\mbfsansLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical sans-serif bold capital lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120673', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120674', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120675', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Xi}"),("unicode-math","\\mbfsansXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120676', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120677', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Pi}"),("unicode-math","\\mbfsansPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120678', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120679', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120680', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Sigma}"),("unicode-math","\\mbfsansSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120681', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120682', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Upsilon}"),("unicode-math","\\mbfsansUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120683', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Phi}"),("unicode-math","\\mbfsansPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120684', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120685', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Psi}"),("unicode-math","\\mbfsansPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120686', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{\\Omega}"),("unicode-math","\\mbfsansOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD CAPITAL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120687', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD NABLA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120688', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\alpha}"),("unicode-math","\\mbfsansalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120689', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\beta}"),("unicode-math","\\mbfsansbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120690', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\gamma}"),("unicode-math","\\mbfsansgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120691', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\delta}"),("unicode-math","\\mbfsansdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120692', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\varepsilon}"),("unicode-math","\\mbfsansepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120693', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\zeta}"),("unicode-math","\\mbfsanszeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120694', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\eta}"),("unicode-math","\\mbfsanseta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120695', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\theta}"),("unicode-math","\\mbfsanstheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120696', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\iota}"),("unicode-math","\\mbfsansiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120697', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\kappa}"),("unicode-math","\\mbfsanskappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120698', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\lambda}"),("unicode-math","\\mbfsanslambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical sans-serif bold small lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120699', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\mu}"),("unicode-math","\\mbfsansmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120700', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\nu}"),("unicode-math","\\mbfsansnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120701', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\xi}"),("unicode-math","\\mbfsansxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120702', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120703', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\pi}"),("unicode-math","\\mbfsanspi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120704', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\rho}"),("unicode-math","\\mbfsansrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120705', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\varsigma}"),("unicode-math","\\mbfsansvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL FINAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120706', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\sigma}"),("unicode-math","\\mbfsanssigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120707', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\tau}"),("unicode-math","\\mbfsanstau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120708', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\upsilon}"),("unicode-math","\\mbfsansupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120709', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\varphi}"),("unicode-math","\\mbfsansphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120710', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\chi}"),("unicode-math","\\mbfsanschi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120711', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\psi}"),("unicode-math","\\mbfsanspsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120712', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\omega}"),("unicode-math","\\mbfsansomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD SMALL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120713', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsanspartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD PARTIAL DIFFERENTIAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120714', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\epsilon}"),("unicode-math","\\mbfsansvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD EPSILON SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120715', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\vartheta}"),("unicode-math","\\mbfsansvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120716', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfsansvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD KAPPA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120717', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\phi}"),("unicode-math","\\mbfsansvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD PHI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120718', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\varrho}"),("unicode-math","\\mbfsansvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD RHO SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120719', commands :: [(Text, Text)]
commands = [("omlmathsfbf","\\mathsfbf{\\varpi}"),("unicode-math","\\mbfsansvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD PI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120720', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansAlpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120721', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansBeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120722', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Gamma}"),("unicode-math","\\mbfitsansGamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120723', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Delta}"),("unicode-math","\\mbfitsansDelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120724', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansEpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120725', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansZeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120726', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansEta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120727', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Theta}"),("unicode-math","\\mbfitsansTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120728', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansIota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120729', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansKappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120730', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Lambda}"),("unicode-math","\\mbfitsansLambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical sans-serif bold italic capital lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120731', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansMu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120732', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansNu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120733', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Xi}"),("unicode-math","\\mbfitsansXi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120734', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansOmicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120735', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Pi}"),("unicode-math","\\mbfitsansPi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120736', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansRho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120737', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansvarTheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120738', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Sigma}"),("unicode-math","\\mbfitsansSigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120739', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansTau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120740', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Upsilon}"),("unicode-math","\\mbfitsansUpsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120741', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Phi}"),("unicode-math","\\mbfitsansPhi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120742', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansChi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120743', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Psi}"),("unicode-math","\\mbfitsansPsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120744', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\Omega}"),("unicode-math","\\mbfitsansOmega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC CAPITAL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120745', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansnabla")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC NABLA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120746', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\alpha}"),("unicode-math","\\mbfitsansalpha")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL ALPHA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120747', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\beta}"),("unicode-math","\\mbfitsansbeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL BETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120748', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\gamma}"),("unicode-math","\\mbfitsansgamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL GAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120749', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\delta}"),("unicode-math","\\mbfitsansdelta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL DELTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120750', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\varepsilon}"),("unicode-math","\\mbfitsansepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL EPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120751', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\zeta}"),("unicode-math","\\mbfitsanszeta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL ZETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120752', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\eta}"),("unicode-math","\\mbfitsanseta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL ETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120753', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\theta}"),("unicode-math","\\mbfitsanstheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL THETA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120754', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\iota}"),("unicode-math","\\mbfitsansiota")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL IOTA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120755', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\kappa}"),("unicode-math","\\mbfitsanskappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL KAPPA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120756', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\lambda}"),("unicode-math","\\mbfitsanslambda")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "mathematical sans-serif bold italic small lambda"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120757', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\mu}"),("unicode-math","\\mbfitsansmu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL MU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120758', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\nu}"),("unicode-math","\\mbfitsansnu")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL NU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120759', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\xi}"),("unicode-math","\\mbfitsansxi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL XI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120760', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansomicron")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL OMICRON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120761', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\pi}"),("unicode-math","\\mbfitsanspi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL PI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120762', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\rho}"),("unicode-math","\\mbfitsansrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL RHO"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120763', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\varsigma}"),("unicode-math","\\mbfitsansvarsigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL FINAL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120764', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\sigma}"),("unicode-math","\\mbfitsanssigma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL SIGMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120765', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\tau}"),("unicode-math","\\mbfitsanstau")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL TAU"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120766', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\upsilon}"),("unicode-math","\\mbfitsansupsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL UPSILON"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120767', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\varphi}"),("unicode-math","\\mbfitsansphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL PHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120768', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\chi}"),("unicode-math","\\mbfitsanschi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL CHI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120769', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\psi}"),("unicode-math","\\mbfitsanspsi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL PSI"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120770', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\omega}"),("unicode-math","\\mbfitsansomega")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC SMALL OMEGA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120771', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsanspartial")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC PARTIAL DIFFERENTIAL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120772', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\epsilon}"),("unicode-math","\\mbfitsansvarepsilon")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC EPSILON SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120773', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\vartheta}"),("unicode-math","\\mbfitsansvartheta")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC THETA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120774', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfitsansvarkappa")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC KAPPA SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120775', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\phi}"),("unicode-math","\\mbfitsansvarphi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC PHI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120776', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\varrho}"),("unicode-math","\\mbfitsansvarrho")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC RHO SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120777', commands :: [(Text, Text)]
commands = [("isomath","\\mathsfbfit{\\varpi}"),("unicode-math","\\mbfitsansvarpi")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL SANS-SERIF BOLD ITALIC PI SYMBOL"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120778', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfDigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD CAPITAL DIGAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120779', commands :: [(Text, Text)]
commands = [("unicode-math","\\mbfdigamma")], category :: TeXSymbolType
category = TeXSymbolType
Alpha, comments :: Text
comments = "MATHEMATICAL BOLD SMALL DIGAMMA"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120782', commands :: [(Text, Text)]
commands = [("base","\\mathbf{0}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 0"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120783', commands :: [(Text, Text)]
commands = [("base","\\mathbf{1}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120784', commands :: [(Text, Text)]
commands = [("base","\\mathbf{2}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120785', commands :: [(Text, Text)]
commands = [("base","\\mathbf{3}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 3"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120786', commands :: [(Text, Text)]
commands = [("base","\\mathbf{4}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 4"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120787', commands :: [(Text, Text)]
commands = [("base","\\mathbf{5}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 5"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120788', commands :: [(Text, Text)]
commands = [("base","\\mathbf{6}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 6"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120789', commands :: [(Text, Text)]
commands = [("base","\\mathbf{7}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 7"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120790', commands :: [(Text, Text)]
commands = [("base","\\mathbf{8}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 8"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120791', commands :: [(Text, Text)]
commands = [("base","\\mathbf{9}")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical bold digit 9"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120792', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{0}"),("unicode-math","\\Bbbzero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 0"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120793', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{1}"),("fourier","\\mathbb{1}"),("dsfont","\\mathds{1}"),("unicode-math","\\Bbbone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120794', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{2}"),("unicode-math","\\Bbbtwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120795', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{3}"),("unicode-math","\\Bbbthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 3"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120796', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{4}"),("unicode-math","\\Bbbfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 4"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120797', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{5}"),("unicode-math","\\Bbbfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 5"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120798', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{6}"),("unicode-math","\\Bbbsix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 6"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120799', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{7}"),("unicode-math","\\Bbbseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 7"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120800', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{8}"),("unicode-math","\\Bbbeight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 8"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120801', commands :: [(Text, Text)]
commands = [("bbold","\\mathbb{9}"),("unicode-math","\\Bbbnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical double-struck digit 9"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120802', commands :: [(Text, Text)]
commands = [("base","\\mathsf{0}"),("unicode-math","\\msanszero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 0"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120803', commands :: [(Text, Text)]
commands = [("base","\\mathsf{1}"),("unicode-math","\\msansone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120804', commands :: [(Text, Text)]
commands = [("base","\\mathsf{2}"),("unicode-math","\\msanstwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120805', commands :: [(Text, Text)]
commands = [("base","\\mathsf{3}"),("unicode-math","\\msansthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 3"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120806', commands :: [(Text, Text)]
commands = [("base","\\mathsf{4}"),("unicode-math","\\msansfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 4"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120807', commands :: [(Text, Text)]
commands = [("base","\\mathsf{5}"),("unicode-math","\\msansfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 5"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120808', commands :: [(Text, Text)]
commands = [("base","\\mathsf{6}"),("unicode-math","\\msanssix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 6"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120809', commands :: [(Text, Text)]
commands = [("base","\\mathsf{7}"),("unicode-math","\\msansseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 7"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120810', commands :: [(Text, Text)]
commands = [("base","\\mathsf{8}"),("unicode-math","\\msanseight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 8"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120811', commands :: [(Text, Text)]
commands = [("base","\\mathsf{9}"),("unicode-math","\\msansnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif digit 9"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120812', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{0}"),("unicode-math","\\mbfsanszero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 0"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120813', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{1}"),("unicode-math","\\mbfsansone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120814', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{2}"),("unicode-math","\\mbfsanstwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120815', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{3}"),("unicode-math","\\mbfsansthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 3"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120816', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{4}"),("unicode-math","\\mbfsansfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 4"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120817', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{5}"),("unicode-math","\\mbfsansfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 5"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120818', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{6}"),("unicode-math","\\mbfsanssix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 6"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120819', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{7}"),("unicode-math","\\mbfsansseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 7"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120820', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{8}"),("unicode-math","\\mbfsanseight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 8"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120821', commands :: [(Text, Text)]
commands = [("mathsfbf","\\mathsfbf{9}"),("unicode-math","\\mbfsansnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical sans-serif bold digit 9"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120822', commands :: [(Text, Text)]
commands = [("base","\\mathtt{0}"),("unicode-math","\\mttzero")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 0"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120823', commands :: [(Text, Text)]
commands = [("base","\\mathtt{1}"),("unicode-math","\\mttone")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 1"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120824', commands :: [(Text, Text)]
commands = [("base","\\mathtt{2}"),("unicode-math","\\mtttwo")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 2"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120825', commands :: [(Text, Text)]
commands = [("base","\\mathtt{3}"),("unicode-math","\\mttthree")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 3"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120826', commands :: [(Text, Text)]
commands = [("base","\\mathtt{4}"),("unicode-math","\\mttfour")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 4"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120827', commands :: [(Text, Text)]
commands = [("base","\\mathtt{5}"),("unicode-math","\\mttfive")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 5"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120828', commands :: [(Text, Text)]
commands = [("base","\\mathtt{6}"),("unicode-math","\\mttsix")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 6"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120829', commands :: [(Text, Text)]
commands = [("base","\\mathtt{7}"),("unicode-math","\\mttseven")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 7"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120830', commands :: [(Text, Text)]
commands = [("base","\\mathtt{8}"),("unicode-math","\\mtteight")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 8"}
, Record :: Char -> [(Text, Text)] -> TeXSymbolType -> Text -> Record
Record {uchar :: Char
uchar = '\120831', commands :: [(Text, Text)]
commands = [("base","\\mathtt{9}"),("unicode-math","\\mttnine")], category :: TeXSymbolType
category = TeXSymbolType
Ord, comments :: Text
comments = "mathematical monospace digit 9"}]