{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2014 Matthew Pickering <matthewtpickering@gmail.com>

This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.

This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
GNU General Public License for more details.

You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-}

{- |

HTML entity definitions as provided by W3C.

The mapping matches the version from 10th April 2014.

The original source can be downloaded from <http://www.w3.org/TR/2014/REC-xml-entity-names-20140410/>.

Note:  I have made one alteration, switching epsilon and varepsilon,
because the meanings of these names in HTML is different from the meanings
in MathML+LaTeX.  See http://www.w3.org/2003/entities/2007doc/#epsilon.

-}

module Text.TeXMath.Readers.MathML.EntityMap (getUnicode) where

import qualified Data.Map as M
import qualified Data.Text as T

-- | Translates MathML entity reference to the corresponding Unicode string.
getUnicode :: T.Text -> Maybe T.Text
getUnicode :: Text -> Maybe Text
getUnicode = (Text -> Map Text Text -> Maybe Text)
-> Map Text Text -> Text -> Maybe Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Map Text Text
entityList

entityList :: M.Map T.Text T.Text
entityList :: Map Text Text
entityList = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  [ (Text
"AElig",Text
"\198")
  , (Text
"AMP",Text
"&")
  , (Text
"Aacute",Text
"\193")
  , (Text
"Abreve",Text
"\258")
  , (Text
"Acirc",Text
"\194")
  , (Text
"Acy",Text
"\1040")
  , (Text
"Afr",Text
"\120068")
  , (Text
"Agrave",Text
"\192")
  , (Text
"Alpha",Text
"\913")
  , (Text
"Amacr",Text
"\256")
  , (Text
"And",Text
"\10835")
  , (Text
"Aogon",Text
"\260")
  , (Text
"Aopf",Text
"\120120")
  , (Text
"ApplyFunction",Text
"\8289")
  , (Text
"Aring",Text
"\197")
  , (Text
"Ascr",Text
"\119964")
  , (Text
"Assign",Text
"\8788")
  , (Text
"Atilde",Text
"\195")
  , (Text
"Auml",Text
"\196")
  , (Text
"Backslash",Text
"\8726")
  , (Text
"Barv",Text
"\10983")
  , (Text
"Barwed",Text
"\8966")
  , (Text
"Bcy",Text
"\1041")
  , (Text
"Because",Text
"\8757")
  , (Text
"Bernoullis",Text
"\8492")
  , (Text
"Beta",Text
"\914")
  , (Text
"Bfr",Text
"\120069")
  , (Text
"Bopf",Text
"\120121")
  , (Text
"Breve",Text
"\728")
  , (Text
"Bscr",Text
"\8492")
  , (Text
"Bumpeq",Text
"\8782")
  , (Text
"CHcy",Text
"\1063")
  , (Text
"COPY",Text
"\169")
  , (Text
"Cacute",Text
"\262")
  , (Text
"Cap",Text
"\8914")
  , (Text
"CapitalDifferentialD",Text
"\8517")
  , (Text
"Cayleys",Text
"\8493")
  , (Text
"Ccaron",Text
"\268")
  , (Text
"Ccedil",Text
"\199")
  , (Text
"Ccirc",Text
"\264")
  , (Text
"Cconint",Text
"\8752")
  , (Text
"Cdot",Text
"\266")
  , (Text
"Cedilla",Text
"\184")
  , (Text
"CenterDot",Text
"\183")
  , (Text
"Cfr",Text
"\8493")
  , (Text
"Chi",Text
"\935")
  , (Text
"CircleDot",Text
"\8857")
  , (Text
"CircleMinus",Text
"\8854")
  , (Text
"CirclePlus",Text
"\8853")
  , (Text
"CircleTimes",Text
"\8855")
  , (Text
"ClockwiseContourIntegral",Text
"\8754")
  , (Text
"CloseCurlyDoubleQuote",Text
"\8221")
  , (Text
"CloseCurlyQuote",Text
"\8217")
  , (Text
"Colon",Text
"\8759")
  , (Text
"Colone",Text
"\10868")
  , (Text
"Congruent",Text
"\8801")
  , (Text
"Conint",Text
"\8751")
  , (Text
"ContourIntegral",Text
"\8750")
  , (Text
"Copf",Text
"\8450")
  , (Text
"Coproduct",Text
"\8720")
  , (Text
"CounterClockwiseContourIntegral",Text
"\8755")
  , (Text
"Cross",Text
"\10799")
  , (Text
"Cscr",Text
"\119966")
  , (Text
"Cup",Text
"\8915")
  , (Text
"CupCap",Text
"\8781")
  , (Text
"DD",Text
"\8517")
  , (Text
"DDotrahd",Text
"\10513")
  , (Text
"DJcy",Text
"\1026")
  , (Text
"DScy",Text
"\1029")
  , (Text
"DZcy",Text
"\1039")
  , (Text
"Dagger",Text
"\8225")
  , (Text
"Darr",Text
"\8609")
  , (Text
"Dashv",Text
"\10980")
  , (Text
"Dcaron",Text
"\270")
  , (Text
"Dcy",Text
"\1044")
  , (Text
"Del",Text
"\8711")
  , (Text
"Delta",Text
"\916")
  , (Text
"Dfr",Text
"\120071")
  , (Text
"DiacriticalAcute",Text
"\180")
  , (Text
"DiacriticalDot",Text
"\729")
  , (Text
"DiacriticalDoubleAcute",Text
"\733")
  , (Text
"DiacriticalGrave",Text
"`")
  , (Text
"DiacriticalTilde",Text
"\732")
  , (Text
"Diamond",Text
"\8900")
  , (Text
"DifferentialD",Text
"\8518")
  , (Text
"Dopf",Text
"\120123")
  , (Text
"Dot",Text
"\168")
  , (Text
"DotDot",Text
" \8412")
  , (Text
"DotEqual",Text
"\8784")
  , (Text
"DoubleContourIntegral",Text
"\8751")
  , (Text
"DoubleDot",Text
"\168")
  , (Text
"DoubleDownArrow",Text
"\8659")
  , (Text
"DoubleLeftArrow",Text
"\8656")
  , (Text
"DoubleLeftRightArrow",Text
"\8660")
  , (Text
"DoubleLeftTee",Text
"\10980")
  , (Text
"DoubleLongLeftArrow",Text
"\10232")
  , (Text
"DoubleLongLeftRightArrow",Text
"\10234")
  , (Text
"DoubleLongRightArrow",Text
"\10233")
  , (Text
"DoubleRightArrow",Text
"\8658")
  , (Text
"DoubleRightTee",Text
"\8872")
  , (Text
"DoubleUpArrow",Text
"\8657")
  , (Text
"DoubleUpDownArrow",Text
"\8661")
  , (Text
"DoubleVerticalBar",Text
"\8741")
  , (Text
"DownArrow",Text
"\8595")
  , (Text
"DownArrowBar",Text
"\10515")
  , (Text
"DownArrowUpArrow",Text
"\8693")
  , (Text
"DownBreve",Text
" \785")
  , (Text
"DownLeftRightVector",Text
"\10576")
  , (Text
"DownLeftTeeVector",Text
"\10590")
  , (Text
"DownLeftVector",Text
"\8637")
  , (Text
"DownLeftVectorBar",Text
"\10582")
  , (Text
"DownRightTeeVector",Text
"\10591")
  , (Text
"DownRightVector",Text
"\8641")
  , (Text
"DownRightVectorBar",Text
"\10583")
  , (Text
"DownTee",Text
"\8868")
  , (Text
"DownTeeArrow",Text
"\8615")
  , (Text
"Downarrow",Text
"\8659")
  , (Text
"Dscr",Text
"\119967")
  , (Text
"Dstrok",Text
"\272")
  , (Text
"ENG",Text
"\330")
  , (Text
"ETH",Text
"\208")
  , (Text
"Eacute",Text
"\201")
  , (Text
"Ecaron",Text
"\282")
  , (Text
"Ecirc",Text
"\202")
  , (Text
"Ecy",Text
"\1069")
  , (Text
"Edot",Text
"\278")
  , (Text
"Efr",Text
"\120072")
  , (Text
"Egrave",Text
"\200")
  , (Text
"Element",Text
"\8712")
  , (Text
"Emacr",Text
"\274")
  , (Text
"EmptySmallSquare",Text
"\9723")
  , (Text
"EmptyVerySmallSquare",Text
"\9643")
  , (Text
"Eogon",Text
"\280")
  , (Text
"Eopf",Text
"\120124")
  , (Text
"Epsilon",Text
"\917")
  , (Text
"Equal",Text
"\10869")
  , (Text
"EqualTilde",Text
"\8770")
  , (Text
"Equilibrium",Text
"\8652")
  , (Text
"Escr",Text
"\8496")
  , (Text
"Esim",Text
"\10867")
  , (Text
"Eta",Text
"\919")
  , (Text
"Euml",Text
"\203")
  , (Text
"Exists",Text
"\8707")
  , (Text
"ExponentialE",Text
"\8519")
  , (Text
"Fcy",Text
"\1060")
  , (Text
"Ffr",Text
"\120073")
  , (Text
"FilledSmallSquare",Text
"\9724")
  , (Text
"FilledVerySmallSquare",Text
"\9642")
  , (Text
"Fopf",Text
"\120125")
  , (Text
"ForAll",Text
"\8704")
  , (Text
"Fouriertrf",Text
"\8497")
  , (Text
"Fscr",Text
"\8497")
  , (Text
"GJcy",Text
"\1027")
  , (Text
"GT",Text
">")
  , (Text
"Gamma",Text
"\915")
  , (Text
"Gammad",Text
"\988")
  , (Text
"Gbreve",Text
"\286")
  , (Text
"Gcedil",Text
"\290")
  , (Text
"Gcirc",Text
"\284")
  , (Text
"Gcy",Text
"\1043")
  , (Text
"Gdot",Text
"\288")
  , (Text
"Gfr",Text
"\120074")
  , (Text
"Gg",Text
"\8921")
  , (Text
"Gopf",Text
"\120126")
  , (Text
"GreaterEqual",Text
"\8805")
  , (Text
"GreaterEqualLess",Text
"\8923")
  , (Text
"GreaterFullEqual",Text
"\8807")
  , (Text
"GreaterGreater",Text
"\10914")
  , (Text
"GreaterLess",Text
"\8823")
  , (Text
"GreaterSlantEqual",Text
"\10878")
  , (Text
"GreaterTilde",Text
"\8819")
  , (Text
"Gscr",Text
"\119970")
  , (Text
"Gt",Text
"\8811")
  , (Text
"HARDcy",Text
"\1066")
  , (Text
"Hacek",Text
"\711")
  , (Text
"Hat",Text
"^")
  , (Text
"Hcirc",Text
"\292")
  , (Text
"Hfr",Text
"\8460")
  , (Text
"HilbertSpace",Text
"\8459")
  , (Text
"Hopf",Text
"\8461")
  , (Text
"HorizontalLine",Text
"\9472")
  , (Text
"Hscr",Text
"\8459")
  , (Text
"Hstrok",Text
"\294")
  , (Text
"HumpDownHump",Text
"\8782")
  , (Text
"HumpEqual",Text
"\8783")
  , (Text
"IEcy",Text
"\1045")
  , (Text
"IJlig",Text
"\306")
  , (Text
"IOcy",Text
"\1025")
  , (Text
"Iacute",Text
"\205")
  , (Text
"Icirc",Text
"\206")
  , (Text
"Icy",Text
"\1048")
  , (Text
"Idot",Text
"\304")
  , (Text
"Ifr",Text
"\8465")
  , (Text
"Igrave",Text
"\204")
  , (Text
"Im",Text
"\8465")
  , (Text
"Imacr",Text
"\298")
  , (Text
"ImaginaryI",Text
"\8520")
  , (Text
"Implies",Text
"\8658")
  , (Text
"Int",Text
"\8748")
  , (Text
"Integral",Text
"\8747")
  , (Text
"Intersection",Text
"\8898")
  , (Text
"InvisibleComma",Text
"\8291")
  , (Text
"InvisibleTimes",Text
"\8290")
  , (Text
"Iogon",Text
"\302")
  , (Text
"Iopf",Text
"\120128")
  , (Text
"Iota",Text
"\921")
  , (Text
"Iscr",Text
"\8464")
  , (Text
"Itilde",Text
"\296")
  , (Text
"Iukcy",Text
"\1030")
  , (Text
"Iuml",Text
"\207")
  , (Text
"Jcirc",Text
"\308")
  , (Text
"Jcy",Text
"\1049")
  , (Text
"Jfr",Text
"\120077")
  , (Text
"Jopf",Text
"\120129")
  , (Text
"Jscr",Text
"\119973")
  , (Text
"Jsercy",Text
"\1032")
  , (Text
"Jukcy",Text
"\1028")
  , (Text
"KHcy",Text
"\1061")
  , (Text
"KJcy",Text
"\1036")
  , (Text
"Kappa",Text
"\922")
  , (Text
"Kcedil",Text
"\310")
  , (Text
"Kcy",Text
"\1050")
  , (Text
"Kfr",Text
"\120078")
  , (Text
"Kopf",Text
"\120130")
  , (Text
"Kscr",Text
"\119974")
  , (Text
"LJcy",Text
"\1033")
  , (Text
"LT",Text
"<")
  , (Text
"Lacute",Text
"\313")
  , (Text
"Lambda",Text
"\923")
  , (Text
"Lang",Text
"\10218")
  , (Text
"Laplacetrf",Text
"\8466")
  , (Text
"Larr",Text
"\8606")
  , (Text
"Lcaron",Text
"\317")
  , (Text
"Lcedil",Text
"\315")
  , (Text
"Lcy",Text
"\1051")
  , (Text
"LeftAngleBracket",Text
"\10216")
  , (Text
"LeftArrow",Text
"\8592")
  , (Text
"LeftArrowBar",Text
"\8676")
  , (Text
"LeftArrowRightArrow",Text
"\8646")
  , (Text
"LeftCeiling",Text
"\8968")
  , (Text
"LeftDoubleBracket",Text
"\10214")
  , (Text
"LeftDownTeeVector",Text
"\10593")
  , (Text
"LeftDownVector",Text
"\8643")
  , (Text
"LeftDownVectorBar",Text
"\10585")
  , (Text
"LeftFloor",Text
"\8970")
  , (Text
"LeftRightArrow",Text
"\8596")
  , (Text
"LeftRightVector",Text
"\10574")
  , (Text
"LeftTee",Text
"\8867")
  , (Text
"LeftTeeArrow",Text
"\8612")
  , (Text
"LeftTeeVector",Text
"\10586")
  , (Text
"LeftTriangle",Text
"\8882")
  , (Text
"LeftTriangleBar",Text
"\10703")
  , (Text
"LeftTriangleEqual",Text
"\8884")
  , (Text
"LeftUpDownVector",Text
"\10577")
  , (Text
"LeftUpTeeVector",Text
"\10592")
  , (Text
"LeftUpVector",Text
"\8639")
  , (Text
"LeftUpVectorBar",Text
"\10584")
  , (Text
"LeftVector",Text
"\8636")
  , (Text
"LeftVectorBar",Text
"\10578")
  , (Text
"Leftarrow",Text
"\8656")
  , (Text
"Leftrightarrow",Text
"\8660")
  , (Text
"LessEqualGreater",Text
"\8922")
  , (Text
"LessFullEqual",Text
"\8806")
  , (Text
"LessGreater",Text
"\8822")
  , (Text
"LessLess",Text
"\10913")
  , (Text
"LessSlantEqual",Text
"\10877")
  , (Text
"LessTilde",Text
"\8818")
  , (Text
"Lfr",Text
"\120079")
  , (Text
"Ll",Text
"\8920")
  , (Text
"Lleftarrow",Text
"\8666")
  , (Text
"Lmidot",Text
"\319")
  , (Text
"LongLeftArrow",Text
"\10229")
  , (Text
"LongLeftRightArrow",Text
"\10231")
  , (Text
"LongRightArrow",Text
"\10230")
  , (Text
"Longleftarrow",Text
"\10232")
  , (Text
"Longleftrightarrow",Text
"\10234")
  , (Text
"Longrightarrow",Text
"\10233")
  , (Text
"Lopf",Text
"\120131")
  , (Text
"LowerLeftArrow",Text
"\8601")
  , (Text
"LowerRightArrow",Text
"\8600")
  , (Text
"Lscr",Text
"\8466")
  , (Text
"Lsh",Text
"\8624")
  , (Text
"Lstrok",Text
"\321")
  , (Text
"Lt",Text
"\8810")
  , (Text
"Map",Text
"\10501")
  , (Text
"Mcy",Text
"\1052")
  , (Text
"MediumSpace",Text
"\8287")
  , (Text
"Mellintrf",Text
"\8499")
  , (Text
"Mfr",Text
"\120080")
  , (Text
"MinusPlus",Text
"\8723")
  , (Text
"Mopf",Text
"\120132")
  , (Text
"Mscr",Text
"\8499")
  , (Text
"Mu",Text
"\924")
  , (Text
"NJcy",Text
"\1034")
  , (Text
"Nacute",Text
"\323")
  , (Text
"Ncaron",Text
"\327")
  , (Text
"Ncedil",Text
"\325")
  , (Text
"Ncy",Text
"\1053")
  , (Text
"NegativeMediumSpace",Text
"\8203")
  , (Text
"NegativeThickSpace",Text
"\8203")
  , (Text
"NegativeThinSpace",Text
"\8203")
  , (Text
"NegativeVeryThinSpace",Text
"\8203")
  , (Text
"NestedGreaterGreater",Text
"\8811")
  , (Text
"NestedLessLess",Text
"\8810")
  , (Text
"NewLine",Text
"\n")
  , (Text
"Nfr",Text
"\120081")
  , (Text
"NoBreak",Text
"\8288")
  , (Text
"NonBreakingSpace",Text
"\160")
  , (Text
"Nopf",Text
"\8469")
  , (Text
"Not",Text
"\10988")
  , (Text
"NotCongruent",Text
"\8802")
  , (Text
"NotCupCap",Text
"\8813")
  , (Text
"NotDoubleVerticalBar",Text
"\8742")
  , (Text
"NotElement",Text
"\8713")
  , (Text
"NotEqual",Text
"\8800")
  , (Text
"NotEqualTilde",Text
"\8770\824")
  , (Text
"NotExists",Text
"\8708")
  , (Text
"NotGreater",Text
"\8815")
  , (Text
"NotGreaterEqual",Text
"\8817")
  , (Text
"NotGreaterFullEqual",Text
"\8807\824")
  , (Text
"NotGreaterGreater",Text
"\8811\824")
  , (Text
"NotGreaterLess",Text
"\8825")
  , (Text
"NotGreaterSlantEqual",Text
"\10878\824")
  , (Text
"NotGreaterTilde",Text
"\8821")
  , (Text
"NotHumpDownHump",Text
"\8782\824")
  , (Text
"NotHumpEqual",Text
"\8783\824")
  , (Text
"NotLeftTriangle",Text
"\8938")
  , (Text
"NotLeftTriangleBar",Text
"\10703\824")
  , (Text
"NotLeftTriangleEqual",Text
"\8940")
  , (Text
"NotLess",Text
"\8814")
  , (Text
"NotLessEqual",Text
"\8816")
  , (Text
"NotLessGreater",Text
"\8824")
  , (Text
"NotLessLess",Text
"\8810\824")
  , (Text
"NotLessSlantEqual",Text
"\10877\824")
  , (Text
"NotLessTilde",Text
"\8820")
  , (Text
"NotNestedGreaterGreater",Text
"\10914\824")
  , (Text
"NotNestedLessLess",Text
"\10913\824")
  , (Text
"NotPrecedes",Text
"\8832")
  , (Text
"NotPrecedesEqual",Text
"\10927\824")
  , (Text
"NotPrecedesSlantEqual",Text
"\8928")
  , (Text
"NotReverseElement",Text
"\8716")
  , (Text
"NotRightTriangle",Text
"\8939")
  , (Text
"NotRightTriangleBar",Text
"\10704\824")
  , (Text
"NotRightTriangleEqual",Text
"\8941")
  , (Text
"NotSquareSubset",Text
"\8847\824")
  , (Text
"NotSquareSubsetEqual",Text
"\8930")
  , (Text
"NotSquareSuperset",Text
"\8848\824")
  , (Text
"NotSquareSupersetEqual",Text
"\8931")
  , (Text
"NotSubset",Text
"\8834\8402")
  , (Text
"NotSubsetEqual",Text
"\8840")
  , (Text
"NotSucceeds",Text
"\8833")
  , (Text
"NotSucceedsEqual",Text
"\10928\824")
  , (Text
"NotSucceedsSlantEqual",Text
"\8929")
  , (Text
"NotSucceedsTilde",Text
"\8831\824")
  , (Text
"NotSuperset",Text
"\8835\8402")
  , (Text
"NotSupersetEqual",Text
"\8841")
  , (Text
"NotTilde",Text
"\8769")
  , (Text
"NotTildeEqual",Text
"\8772")
  , (Text
"NotTildeFullEqual",Text
"\8775")
  , (Text
"NotTildeTilde",Text
"\8777")
  , (Text
"NotVerticalBar",Text
"\8740")
  , (Text
"Nscr",Text
"\119977")
  , (Text
"Ntilde",Text
"\209")
  , (Text
"Nu",Text
"\925")
  , (Text
"OElig",Text
"\338")
  , (Text
"Oacute",Text
"\211")
  , (Text
"Ocirc",Text
"\212")
  , (Text
"Ocy",Text
"\1054")
  , (Text
"Odblac",Text
"\336")
  , (Text
"Ofr",Text
"\120082")
  , (Text
"Ograve",Text
"\210")
  , (Text
"Omacr",Text
"\332")
  , (Text
"Omega",Text
"\937")
  , (Text
"Omicron",Text
"\927")
  , (Text
"Oopf",Text
"\120134")
  , (Text
"OpenCurlyDoubleQuote",Text
"\8220")
  , (Text
"OpenCurlyQuote",Text
"\8216")
  , (Text
"Or",Text
"\10836")
  , (Text
"Oscr",Text
"\119978")
  , (Text
"Oslash",Text
"\216")
  , (Text
"Otilde",Text
"\213")
  , (Text
"Otimes",Text
"\10807")
  , (Text
"Ouml",Text
"\214")
  , (Text
"OverBar",Text
"\8254")
  , (Text
"OverBrace",Text
"\9182")
  , (Text
"OverBracket",Text
"\9140")
  , (Text
"OverParenthesis",Text
"\9180")
  , (Text
"PartialD",Text
"\8706")
  , (Text
"Pcy",Text
"\1055")
  , (Text
"Pfr",Text
"\120083")
  , (Text
"Phi",Text
"\934")
  , (Text
"Pi",Text
"\928")
  , (Text
"PlusMinus",Text
"\177")
  , (Text
"Poincareplane",Text
"\8460")
  , (Text
"Popf",Text
"\8473")
  , (Text
"Pr",Text
"\10939")
  , (Text
"Precedes",Text
"\8826")
  , (Text
"PrecedesEqual",Text
"\10927")
  , (Text
"PrecedesSlantEqual",Text
"\8828")
  , (Text
"PrecedesTilde",Text
"\8830")
  , (Text
"Prime",Text
"\8243")
  , (Text
"Product",Text
"\8719")
  , (Text
"Proportion",Text
"\8759")
  , (Text
"Proportional",Text
"\8733")
  , (Text
"Pscr",Text
"\119979")
  , (Text
"Psi",Text
"\936")
  , (Text
"QUOT",Text
"\"")
  , (Text
"Qfr",Text
"\120084")
  , (Text
"Qopf",Text
"\8474")
  , (Text
"Qscr",Text
"\119980")
  , (Text
"RBarr",Text
"\10512")
  , (Text
"REG",Text
"\174")
  , (Text
"Racute",Text
"\340")
  , (Text
"Rang",Text
"\10219")
  , (Text
"Rarr",Text
"\8608")
  , (Text
"Rarrtl",Text
"\10518")
  , (Text
"Rcaron",Text
"\344")
  , (Text
"Rcedil",Text
"\342")
  , (Text
"Rcy",Text
"\1056")
  , (Text
"Re",Text
"\8476")
  , (Text
"ReverseElement",Text
"\8715")
  , (Text
"ReverseEquilibrium",Text
"\8651")
  , (Text
"ReverseUpEquilibrium",Text
"\10607")
  , (Text
"Rfr",Text
"\8476")
  , (Text
"Rho",Text
"\929")
  , (Text
"RightAngleBracket",Text
"\10217")
  , (Text
"RightArrow",Text
"\8594")
  , (Text
"RightArrowBar",Text
"\8677")
  , (Text
"RightArrowLeftArrow",Text
"\8644")
  , (Text
"RightCeiling",Text
"\8969")
  , (Text
"RightDoubleBracket",Text
"\10215")
  , (Text
"RightDownTeeVector",Text
"\10589")
  , (Text
"RightDownVector",Text
"\8642")
  , (Text
"RightDownVectorBar",Text
"\10581")
  , (Text
"RightFloor",Text
"\8971")
  , (Text
"RightTee",Text
"\8866")
  , (Text
"RightTeeArrow",Text
"\8614")
  , (Text
"RightTeeVector",Text
"\10587")
  , (Text
"RightTriangle",Text
"\8883")
  , (Text
"RightTriangleBar",Text
"\10704")
  , (Text
"RightTriangleEqual",Text
"\8885")
  , (Text
"RightUpDownVector",Text
"\10575")
  , (Text
"RightUpTeeVector",Text
"\10588")
  , (Text
"RightUpVector",Text
"\8638")
  , (Text
"RightUpVectorBar",Text
"\10580")
  , (Text
"RightVector",Text
"\8640")
  , (Text
"RightVectorBar",Text
"\10579")
  , (Text
"Rightarrow",Text
"\8658")
  , (Text
"Ropf",Text
"\8477")
  , (Text
"RoundImplies",Text
"\10608")
  , (Text
"Rrightarrow",Text
"\8667")
  , (Text
"Rscr",Text
"\8475")
  , (Text
"Rsh",Text
"\8625")
  , (Text
"RuleDelayed",Text
"\10740")
  , (Text
"SHCHcy",Text
"\1065")
  , (Text
"SHcy",Text
"\1064")
  , (Text
"SOFTcy",Text
"\1068")
  , (Text
"Sacute",Text
"\346")
  , (Text
"Sc",Text
"\10940")
  , (Text
"Scaron",Text
"\352")
  , (Text
"Scedil",Text
"\350")
  , (Text
"Scirc",Text
"\348")
  , (Text
"Scy",Text
"\1057")
  , (Text
"Sfr",Text
"\120086")
  , (Text
"ShortDownArrow",Text
"\8595")
  , (Text
"ShortLeftArrow",Text
"\8592")
  , (Text
"ShortRightArrow",Text
"\8594")
  , (Text
"ShortUpArrow",Text
"\8593")
  , (Text
"Sigma",Text
"\931")
  , (Text
"SmallCircle",Text
"\8728")
  , (Text
"Sopf",Text
"\120138")
  , (Text
"Sqrt",Text
"\8730")
  , (Text
"Square",Text
"\9633")
  , (Text
"SquareIntersection",Text
"\8851")
  , (Text
"SquareSubset",Text
"\8847")
  , (Text
"SquareSubsetEqual",Text
"\8849")
  , (Text
"SquareSuperset",Text
"\8848")
  , (Text
"SquareSupersetEqual",Text
"\8850")
  , (Text
"SquareUnion",Text
"\8852")
  , (Text
"Sscr",Text
"\119982")
  , (Text
"Star",Text
"\8902")
  , (Text
"Sub",Text
"\8912")
  , (Text
"Subset",Text
"\8912")
  , (Text
"SubsetEqual",Text
"\8838")
  , (Text
"Succeeds",Text
"\8827")
  , (Text
"SucceedsEqual",Text
"\10928")
  , (Text
"SucceedsSlantEqual",Text
"\8829")
  , (Text
"SucceedsTilde",Text
"\8831")
  , (Text
"SuchThat",Text
"\8715")
  , (Text
"Sum",Text
"\8721")
  , (Text
"Sup",Text
"\8913")
  , (Text
"Superset",Text
"\8835")
  , (Text
"SupersetEqual",Text
"\8839")
  , (Text
"Supset",Text
"\8913")
  , (Text
"THORN",Text
"\222")
  , (Text
"TRADE",Text
"\8482")
  , (Text
"TSHcy",Text
"\1035")
  , (Text
"TScy",Text
"\1062")
  , (Text
"Tab",Text
"\t")
  , (Text
"Tau",Text
"\932")
  , (Text
"Tcaron",Text
"\356")
  , (Text
"Tcedil",Text
"\354")
  , (Text
"Tcy",Text
"\1058")
  , (Text
"Tfr",Text
"\120087")
  , (Text
"Therefore",Text
"\8756")
  , (Text
"Theta",Text
"\920")
  , (Text
"ThickSpace",Text
"\8287\8202")
  , (Text
"ThinSpace",Text
"\8201")
  , (Text
"Tilde",Text
"\8764")
  , (Text
"TildeEqual",Text
"\8771")
  , (Text
"TildeFullEqual",Text
"\8773")
  , (Text
"TildeTilde",Text
"\8776")
  , (Text
"Topf",Text
"\120139")
  , (Text
"TripleDot",Text
" \8411")
  , (Text
"Tscr",Text
"\119983")
  , (Text
"Tstrok",Text
"\358")
  , (Text
"Uacute",Text
"\218")
  , (Text
"Uarr",Text
"\8607")
  , (Text
"Uarrocir",Text
"\10569")
  , (Text
"Ubrcy",Text
"\1038")
  , (Text
"Ubreve",Text
"\364")
  , (Text
"Ucirc",Text
"\219")
  , (Text
"Ucy",Text
"\1059")
  , (Text
"Udblac",Text
"\368")
  , (Text
"Ufr",Text
"\120088")
  , (Text
"Ugrave",Text
"\217")
  , (Text
"Umacr",Text
"\362")
  , (Text
"UnderBar",Text
"_")
  , (Text
"UnderBrace",Text
"\9183")
  , (Text
"UnderBracket",Text
"\9141")
  , (Text
"UnderParenthesis",Text
"\9181")
  , (Text
"Union",Text
"\8899")
  , (Text
"UnionPlus",Text
"\8846")
  , (Text
"Uogon",Text
"\370")
  , (Text
"Uopf",Text
"\120140")
  , (Text
"UpArrow",Text
"\8593")
  , (Text
"UpArrowBar",Text
"\10514")
  , (Text
"UpArrowDownArrow",Text
"\8645")
  , (Text
"UpDownArrow",Text
"\8597")
  , (Text
"UpEquilibrium",Text
"\10606")
  , (Text
"UpTee",Text
"\8869")
  , (Text
"UpTeeArrow",Text
"\8613")
  , (Text
"Uparrow",Text
"\8657")
  , (Text
"Updownarrow",Text
"\8661")
  , (Text
"UpperLeftArrow",Text
"\8598")
  , (Text
"UpperRightArrow",Text
"\8599")
  , (Text
"Upsi",Text
"\978")
  , (Text
"Upsilon",Text
"\933")
  , (Text
"Uring",Text
"\366")
  , (Text
"Uscr",Text
"\119984")
  , (Text
"Utilde",Text
"\360")
  , (Text
"Uuml",Text
"\220")
  , (Text
"VDash",Text
"\8875")
  , (Text
"Vbar",Text
"\10987")
  , (Text
"Vcy",Text
"\1042")
  , (Text
"Vdash",Text
"\8873")
  , (Text
"Vdashl",Text
"\10982")
  , (Text
"Vee",Text
"\8897")
  , (Text
"Verbar",Text
"\8214")
  , (Text
"Vert",Text
"\8214")
  , (Text
"VerticalBar",Text
"\8739")
  , (Text
"VerticalLine",Text
"|")
  , (Text
"VerticalSeparator",Text
"\10072")
  , (Text
"VerticalTilde",Text
"\8768")
  , (Text
"VeryThinSpace",Text
"\8202")
  , (Text
"Vfr",Text
"\120089")
  , (Text
"Vopf",Text
"\120141")
  , (Text
"Vscr",Text
"\119985")
  , (Text
"Vvdash",Text
"\8874")
  , (Text
"Wcirc",Text
"\372")
  , (Text
"Wedge",Text
"\8896")
  , (Text
"Wfr",Text
"\120090")
  , (Text
"Wopf",Text
"\120142")
  , (Text
"Wscr",Text
"\119986")
  , (Text
"Xfr",Text
"\120091")
  , (Text
"Xi",Text
"\926")
  , (Text
"Xopf",Text
"\120143")
  , (Text
"Xscr",Text
"\119987")
  , (Text
"YAcy",Text
"\1071")
  , (Text
"YIcy",Text
"\1031")
  , (Text
"YUcy",Text
"\1070")
  , (Text
"Yacute",Text
"\221")
  , (Text
"Ycirc",Text
"\374")
  , (Text
"Ycy",Text
"\1067")
  , (Text
"Yfr",Text
"\120092")
  , (Text
"Yopf",Text
"\120144")
  , (Text
"Yscr",Text
"\119988")
  , (Text
"Yuml",Text
"\376")
  , (Text
"ZHcy",Text
"\1046")
  , (Text
"Zacute",Text
"\377")
  , (Text
"Zcaron",Text
"\381")
  , (Text
"Zcy",Text
"\1047")
  , (Text
"Zdot",Text
"\379")
  , (Text
"ZeroWidthSpace",Text
"\8203")
  , (Text
"Zeta",Text
"\918")
  , (Text
"Zfr",Text
"\8488")
  , (Text
"Zopf",Text
"\8484")
  , (Text
"Zscr",Text
"\119989")
  , (Text
"aacute",Text
"\225")
  , (Text
"abreve",Text
"\259")
  , (Text
"ac",Text
"\8766")
  , (Text
"acE",Text
"\8766\819")
  , (Text
"acd",Text
"\8767")
  , (Text
"acirc",Text
"\226")
  , (Text
"acute",Text
"\180")
  , (Text
"acy",Text
"\1072")
  , (Text
"aelig",Text
"\230")
  , (Text
"af",Text
"\8289")
  , (Text
"afr",Text
"\120094")
  , (Text
"agrave",Text
"\224")
  , (Text
"alefsym",Text
"\8501")
  , (Text
"aleph",Text
"\8501")
  , (Text
"alpha",Text
"\945")
  , (Text
"amacr",Text
"\257")
  , (Text
"amalg",Text
"\10815")
  , (Text
"amp",Text
"&")
  , (Text
"and",Text
"\8743")
  , (Text
"andand",Text
"\10837")
  , (Text
"andd",Text
"\10844")
  , (Text
"andslope",Text
"\10840")
  , (Text
"andv",Text
"\10842")
  , (Text
"ang",Text
"\8736")
  , (Text
"ange",Text
"\10660")
  , (Text
"angle",Text
"\8736")
  , (Text
"angmsd",Text
"\8737")
  , (Text
"angmsdaa",Text
"\10664")
  , (Text
"angmsdab",Text
"\10665")
  , (Text
"angmsdac",Text
"\10666")
  , (Text
"angmsdad",Text
"\10667")
  , (Text
"angmsdae",Text
"\10668")
  , (Text
"angmsdaf",Text
"\10669")
  , (Text
"angmsdag",Text
"\10670")
  , (Text
"angmsdah",Text
"\10671")
  , (Text
"angrt",Text
"\8735")
  , (Text
"angrtvb",Text
"\8894")
  , (Text
"angrtvbd",Text
"\10653")
  , (Text
"angsph",Text
"\8738")
  , (Text
"angst",Text
"\197")
  , (Text
"angzarr",Text
"\9084")
  , (Text
"aogon",Text
"\261")
  , (Text
"aopf",Text
"\120146")
  , (Text
"ap",Text
"\8776")
  , (Text
"apE",Text
"\10864")
  , (Text
"apacir",Text
"\10863")
  , (Text
"ape",Text
"\8778")
  , (Text
"apid",Text
"\8779")
  , (Text
"apos",Text
"'")
  , (Text
"approx",Text
"\8776")
  , (Text
"approxeq",Text
"\8778")
  , (Text
"aring",Text
"\229")
  , (Text
"ascr",Text
"\119990")
  , (Text
"ast",Text
"*")
  , (Text
"asymp",Text
"\8776")
  , (Text
"asympeq",Text
"\8781")
  , (Text
"atilde",Text
"\227")
  , (Text
"auml",Text
"\228")
  , (Text
"awconint",Text
"\8755")
  , (Text
"awint",Text
"\10769")
  , (Text
"bNot",Text
"\10989")
  , (Text
"backcong",Text
"\8780")
  , (Text
"backepsilon",Text
"\1014")
  , (Text
"backprime",Text
"\8245")
  , (Text
"backsim",Text
"\8765")
  , (Text
"backsimeq",Text
"\8909")
  , (Text
"barvee",Text
"\8893")
  , (Text
"barwed",Text
"\8965")
  , (Text
"barwedge",Text
"\8965")
  , (Text
"bbrk",Text
"\9141")
  , (Text
"bbrktbrk",Text
"\9142")
  , (Text
"bcong",Text
"\8780")
  , (Text
"bcy",Text
"\1073")
  , (Text
"bdquo",Text
"\8222")
  , (Text
"becaus",Text
"\8757")
  , (Text
"because",Text
"\8757")
  , (Text
"bemptyv",Text
"\10672")
  , (Text
"bepsi",Text
"\1014")
  , (Text
"bernou",Text
"\8492")
  , (Text
"beta",Text
"\946")
  , (Text
"beth",Text
"\8502")
  , (Text
"between",Text
"\8812")
  , (Text
"bfr",Text
"\120095")
  , (Text
"bigcap",Text
"\8898")
  , (Text
"bigcirc",Text
"\9711")
  , (Text
"bigcup",Text
"\8899")
  , (Text
"bigodot",Text
"\10752")
  , (Text
"bigoplus",Text
"\10753")
  , (Text
"bigotimes",Text
"\10754")
  , (Text
"bigsqcup",Text
"\10758")
  , (Text
"bigstar",Text
"\9733")
  , (Text
"bigtriangledown",Text
"\9661")
  , (Text
"bigtriangleup",Text
"\9651")
  , (Text
"biguplus",Text
"\10756")
  , (Text
"bigvee",Text
"\8897")
  , (Text
"bigwedge",Text
"\8896")
  , (Text
"bkarow",Text
"\10509")
  , (Text
"blacklozenge",Text
"\10731")
  , (Text
"blacksquare",Text
"\9642")
  , (Text
"blacktriangle",Text
"\9652")
  , (Text
"blacktriangledown",Text
"\9662")
  , (Text
"blacktriangleleft",Text
"\9666")
  , (Text
"blacktriangleright",Text
"\9656")
  , (Text
"blank",Text
"\9251")
  , (Text
"blk12",Text
"\9618")
  , (Text
"blk14",Text
"\9617")
  , (Text
"blk34",Text
"\9619")
  , (Text
"block",Text
"\9608")
  , (Text
"bne",Text
"=\8421")
  , (Text
"bnequiv",Text
"\8801\8421")
  , (Text
"bnot",Text
"\8976")
  , (Text
"bopf",Text
"\120147")
  , (Text
"bot",Text
"\8869")
  , (Text
"bottom",Text
"\8869")
  , (Text
"bowtie",Text
"\8904")
  , (Text
"boxDL",Text
"\9559")
  , (Text
"boxDR",Text
"\9556")
  , (Text
"boxDl",Text
"\9558")
  , (Text
"boxDr",Text
"\9555")
  , (Text
"boxH",Text
"\9552")
  , (Text
"boxHD",Text
"\9574")
  , (Text
"boxHU",Text
"\9577")
  , (Text
"boxHd",Text
"\9572")
  , (Text
"boxHu",Text
"\9575")
  , (Text
"boxUL",Text
"\9565")
  , (Text
"boxUR",Text
"\9562")
  , (Text
"boxUl",Text
"\9564")
  , (Text
"boxUr",Text
"\9561")
  , (Text
"boxV",Text
"\9553")
  , (Text
"boxVH",Text
"\9580")
  , (Text
"boxVL",Text
"\9571")
  , (Text
"boxVR",Text
"\9568")
  , (Text
"boxVh",Text
"\9579")
  , (Text
"boxVl",Text
"\9570")
  , (Text
"boxVr",Text
"\9567")
  , (Text
"boxbox",Text
"\10697")
  , (Text
"boxdL",Text
"\9557")
  , (Text
"boxdR",Text
"\9554")
  , (Text
"boxdl",Text
"\9488")
  , (Text
"boxdr",Text
"\9484")
  , (Text
"boxh",Text
"\9472")
  , (Text
"boxhD",Text
"\9573")
  , (Text
"boxhU",Text
"\9576")
  , (Text
"boxhd",Text
"\9516")
  , (Text
"boxhu",Text
"\9524")
  , (Text
"boxminus",Text
"\8863")
  , (Text
"boxplus",Text
"\8862")
  , (Text
"boxtimes",Text
"\8864")
  , (Text
"boxuL",Text
"\9563")
  , (Text
"boxuR",Text
"\9560")
  , (Text
"boxul",Text
"\9496")
  , (Text
"boxur",Text
"\9492")
  , (Text
"boxv",Text
"\9474")
  , (Text
"boxvH",Text
"\9578")
  , (Text
"boxvL",Text
"\9569")
  , (Text
"boxvR",Text
"\9566")
  , (Text
"boxvh",Text
"\9532")
  , (Text
"boxvl",Text
"\9508")
  , (Text
"boxvr",Text
"\9500")
  , (Text
"bprime",Text
"\8245")
  , (Text
"breve",Text
"\728")
  , (Text
"brvbar",Text
"\166")
  , (Text
"bscr",Text
"\119991")
  , (Text
"bsemi",Text
"\8271")
  , (Text
"bsim",Text
"\8765")
  , (Text
"bsime",Text
"\8909")
  , (Text
"bsol",Text
"\\")
  , (Text
"bsolb",Text
"\10693")
  , (Text
"bsolhsub",Text
"\10184")
  , (Text
"bull",Text
"\8226")
  , (Text
"bullet",Text
"\8226")
  , (Text
"bump",Text
"\8782")
  , (Text
"bumpE",Text
"\10926")
  , (Text
"bumpe",Text
"\8783")
  , (Text
"bumpeq",Text
"\8783")
  , (Text
"cacute",Text
"\263")
  , (Text
"cap",Text
"\8745")
  , (Text
"capand",Text
"\10820")
  , (Text
"capbrcup",Text
"\10825")
  , (Text
"capcap",Text
"\10827")
  , (Text
"capcup",Text
"\10823")
  , (Text
"capdot",Text
"\10816")
  , (Text
"caps",Text
"\8745\65024")
  , (Text
"caret",Text
"\8257")
  , (Text
"caron",Text
"\711")
  , (Text
"ccaps",Text
"\10829")
  , (Text
"ccaron",Text
"\269")
  , (Text
"ccedil",Text
"\231")
  , (Text
"ccirc",Text
"\265")
  , (Text
"ccups",Text
"\10828")
  , (Text
"ccupssm",Text
"\10832")
  , (Text
"cdot",Text
"\267")
  , (Text
"cedil",Text
"\184")
  , (Text
"cemptyv",Text
"\10674")
  , (Text
"cent",Text
"\162")
  , (Text
"centerdot",Text
"\183")
  , (Text
"cfr",Text
"\120096")
  , (Text
"chcy",Text
"\1095")
  , (Text
"check",Text
"\10003")
  , (Text
"checkmark",Text
"\10003")
  , (Text
"chi",Text
"\967")
  , (Text
"cir",Text
"\9675")
  , (Text
"cirE",Text
"\10691")
  , (Text
"circ",Text
"\710")
  , (Text
"circeq",Text
"\8791")
  , (Text
"circlearrowleft",Text
"\8634")
  , (Text
"circlearrowright",Text
"\8635")
  , (Text
"circledR",Text
"\174")
  , (Text
"circledS",Text
"\9416")
  , (Text
"circledast",Text
"\8859")
  , (Text
"circledcirc",Text
"\8858")
  , (Text
"circleddash",Text
"\8861")
  , (Text
"cire",Text
"\8791")
  , (Text
"cirfnint",Text
"\10768")
  , (Text
"cirmid",Text
"\10991")
  , (Text
"cirscir",Text
"\10690")
  , (Text
"clubs",Text
"\9827")
  , (Text
"clubsuit",Text
"\9827")
  , (Text
"colon",Text
":")
  , (Text
"colone",Text
"\8788")
  , (Text
"coloneq",Text
"\8788")
  , (Text
"comma",Text
",")
  , (Text
"commat",Text
"@")
  , (Text
"comp",Text
"\8705")
  , (Text
"compfn",Text
"\8728")
  , (Text
"complement",Text
"\8705")
  , (Text
"complexes",Text
"\8450")
  , (Text
"cong",Text
"\8773")
  , (Text
"congdot",Text
"\10861")
  , (Text
"conint",Text
"\8750")
  , (Text
"copf",Text
"\120148")
  , (Text
"coprod",Text
"\8720")
  , (Text
"copy",Text
"\169")
  , (Text
"copysr",Text
"\8471")
  , (Text
"crarr",Text
"\8629")
  , (Text
"cross",Text
"\10007")
  , (Text
"cscr",Text
"\119992")
  , (Text
"csub",Text
"\10959")
  , (Text
"csube",Text
"\10961")
  , (Text
"csup",Text
"\10960")
  , (Text
"csupe",Text
"\10962")
  , (Text
"ctdot",Text
"\8943")
  , (Text
"cudarrl",Text
"\10552")
  , (Text
"cudarrr",Text
"\10549")
  , (Text
"cuepr",Text
"\8926")
  , (Text
"cuesc",Text
"\8927")
  , (Text
"cularr",Text
"\8630")
  , (Text
"cularrp",Text
"\10557")
  , (Text
"cup",Text
"\8746")
  , (Text
"cupbrcap",Text
"\10824")
  , (Text
"cupcap",Text
"\10822")
  , (Text
"cupcup",Text
"\10826")
  , (Text
"cupdot",Text
"\8845")
  , (Text
"cupor",Text
"\10821")
  , (Text
"cups",Text
"\8746\65024")
  , (Text
"curarr",Text
"\8631")
  , (Text
"curarrm",Text
"\10556")
  , (Text
"curlyeqprec",Text
"\8926")
  , (Text
"curlyeqsucc",Text
"\8927")
  , (Text
"curlyvee",Text
"\8910")
  , (Text
"curlywedge",Text
"\8911")
  , (Text
"curren",Text
"\164")
  , (Text
"curvearrowleft",Text
"\8630")
  , (Text
"curvearrowright",Text
"\8631")
  , (Text
"cuvee",Text
"\8910")
  , (Text
"cuwed",Text
"\8911")
  , (Text
"cwconint",Text
"\8754")
  , (Text
"cwint",Text
"\8753")
  , (Text
"cylcty",Text
"\9005")
  , (Text
"dArr",Text
"\8659")
  , (Text
"dHar",Text
"\10597")
  , (Text
"dagger",Text
"\8224")
  , (Text
"daleth",Text
"\8504")
  , (Text
"darr",Text
"\8595")
  , (Text
"dash",Text
"\8208")
  , (Text
"dashv",Text
"\8867")
  , (Text
"dbkarow",Text
"\10511")
  , (Text
"dblac",Text
"\733")
  , (Text
"dcaron",Text
"\271")
  , (Text
"dcy",Text
"\1076")
  , (Text
"dd",Text
"\8518")
  , (Text
"ddagger",Text
"\8225")
  , (Text
"ddarr",Text
"\8650")
  , (Text
"ddotseq",Text
"\10871")
  , (Text
"deg",Text
"\176")
  , (Text
"delta",Text
"\948")
  , (Text
"demptyv",Text
"\10673")
  , (Text
"dfisht",Text
"\10623")
  , (Text
"dfr",Text
"\120097")
  , (Text
"dharl",Text
"\8643")
  , (Text
"dharr",Text
"\8642")
  , (Text
"diam",Text
"\8900")
  , (Text
"diamond",Text
"\8900")
  , (Text
"diamondsuit",Text
"\9830")
  , (Text
"diams",Text
"\9830")
  , (Text
"die",Text
"\168")
  , (Text
"digamma",Text
"\989")
  , (Text
"disin",Text
"\8946")
  , (Text
"div",Text
"\247")
  , (Text
"divide",Text
"\247")
  , (Text
"divideontimes",Text
"\8903")
  , (Text
"divonx",Text
"\8903")
  , (Text
"djcy",Text
"\1106")
  , (Text
"dlcorn",Text
"\8990")
  , (Text
"dlcrop",Text
"\8973")
  , (Text
"dollar",Text
"$")
  , (Text
"dopf",Text
"\120149")
  , (Text
"dot",Text
"\729")
  , (Text
"doteq",Text
"\8784")
  , (Text
"doteqdot",Text
"\8785")
  , (Text
"dotminus",Text
"\8760")
  , (Text
"dotplus",Text
"\8724")
  , (Text
"dotsquare",Text
"\8865")
  , (Text
"doublebarwedge",Text
"\8966")
  , (Text
"downarrow",Text
"\8595")
  , (Text
"downdownarrows",Text
"\8650")
  , (Text
"downharpoonleft",Text
"\8643")
  , (Text
"downharpoonright",Text
"\8642")
  , (Text
"drbkarow",Text
"\10512")
  , (Text
"drcorn",Text
"\8991")
  , (Text
"drcrop",Text
"\8972")
  , (Text
"dscr",Text
"\119993")
  , (Text
"dscy",Text
"\1109")
  , (Text
"dsol",Text
"\10742")
  , (Text
"dstrok",Text
"\273")
  , (Text
"dtdot",Text
"\8945")
  , (Text
"dtri",Text
"\9663")
  , (Text
"dtrif",Text
"\9662")
  , (Text
"duarr",Text
"\8693")
  , (Text
"duhar",Text
"\10607")
  , (Text
"dwangle",Text
"\10662")
  , (Text
"dzcy",Text
"\1119")
  , (Text
"dzigrarr",Text
"\10239")
  , (Text
"eDDot",Text
"\10871")
  , (Text
"eDot",Text
"\8785")
  , (Text
"eacute",Text
"\233")
  , (Text
"easter",Text
"\10862")
  , (Text
"ecaron",Text
"\283")
  , (Text
"ecir",Text
"\8790")
  , (Text
"ecirc",Text
"\234")
  , (Text
"ecolon",Text
"\8789")
  , (Text
"ecy",Text
"\1101")
  , (Text
"edot",Text
"\279")
  , (Text
"ee",Text
"\8519")
  , (Text
"efDot",Text
"\8786")
  , (Text
"efr",Text
"\120098")
  , (Text
"eg",Text
"\10906")
  , (Text
"egrave",Text
"\232")
  , (Text
"egs",Text
"\10902")
  , (Text
"egsdot",Text
"\10904")
  , (Text
"el",Text
"\10905")
  , (Text
"elinters",Text
"\9191")
  , (Text
"ell",Text
"\8467")
  , (Text
"els",Text
"\10901")
  , (Text
"elsdot",Text
"\10903")
  , (Text
"emacr",Text
"\275")
  , (Text
"empty",Text
"\8709")
  , (Text
"emptyset",Text
"\8709")
  , (Text
"emptyv",Text
"\8709")
  , (Text
"emsp",Text
"\8195")
  , (Text
"emsp13",Text
"\8196")
  , (Text
"emsp14",Text
"\8197")
  , (Text
"eng",Text
"\331")
  , (Text
"ensp",Text
"\8194")
  , (Text
"eogon",Text
"\281")
  , (Text
"eopf",Text
"\120150")
  , (Text
"epar",Text
"\8917")
  , (Text
"eparsl",Text
"\10723")
  , (Text
"eplus",Text
"\10865")
  , (Text
"epsi",Text
"\949")
  , (Text
"epsilon",Text
"\1013")
  , (Text
"epsiv",Text
"\1013")
  , (Text
"eqcirc",Text
"\8790")
  , (Text
"eqcolon",Text
"\8789")
  , (Text
"eqsim",Text
"\8770")
  , (Text
"eqslantgtr",Text
"\10902")
  , (Text
"eqslantless",Text
"\10901")
  , (Text
"equals",Text
"=")
  , (Text
"equest",Text
"\8799")
  , (Text
"equiv",Text
"\8801")
  , (Text
"equivDD",Text
"\10872")
  , (Text
"eqvparsl",Text
"\10725")
  , (Text
"erDot",Text
"\8787")
  , (Text
"erarr",Text
"\10609")
  , (Text
"escr",Text
"\8495")
  , (Text
"esdot",Text
"\8784")
  , (Text
"esim",Text
"\8770")
  , (Text
"eta",Text
"\951")
  , (Text
"eth",Text
"\240")
  , (Text
"euml",Text
"\235")
  , (Text
"euro",Text
"\8364")
  , (Text
"excl",Text
"!")
  , (Text
"exist",Text
"\8707")
  , (Text
"expectation",Text
"\8496")
  , (Text
"exponentiale",Text
"\8519")
  , (Text
"fallingdotseq",Text
"\8786")
  , (Text
"fcy",Text
"\1092")
  , (Text
"female",Text
"\9792")
  , (Text
"ffilig",Text
"\64259")
  , (Text
"fflig",Text
"\64256")
  , (Text
"ffllig",Text
"\64260")
  , (Text
"ffr",Text
"\120099")
  , (Text
"filig",Text
"\64257")
  , (Text
"fjlig",Text
"fj")
  , (Text
"flat",Text
"\9837")
  , (Text
"fllig",Text
"\64258")
  , (Text
"fltns",Text
"\9649")
  , (Text
"fnof",Text
"\402")
  , (Text
"fopf",Text
"\120151")
  , (Text
"forall",Text
"\8704")
  , (Text
"fork",Text
"\8916")
  , (Text
"forkv",Text
"\10969")
  , (Text
"fpartint",Text
"\10765")
  , (Text
"frac12",Text
"\189")
  , (Text
"frac13",Text
"\8531")
  , (Text
"frac14",Text
"\188")
  , (Text
"frac15",Text
"\8533")
  , (Text
"frac16",Text
"\8537")
  , (Text
"frac18",Text
"\8539")
  , (Text
"frac23",Text
"\8532")
  , (Text
"frac25",Text
"\8534")
  , (Text
"frac34",Text
"\190")
  , (Text
"frac35",Text
"\8535")
  , (Text
"frac38",Text
"\8540")
  , (Text
"frac45",Text
"\8536")
  , (Text
"frac56",Text
"\8538")
  , (Text
"frac58",Text
"\8541")
  , (Text
"frac78",Text
"\8542")
  , (Text
"frasl",Text
"\8260")
  , (Text
"frown",Text
"\8994")
  , (Text
"fscr",Text
"\119995")
  , (Text
"gE",Text
"\8807")
  , (Text
"gEl",Text
"\10892")
  , (Text
"gacute",Text
"\501")
  , (Text
"gamma",Text
"\947")
  , (Text
"gammad",Text
"\989")
  , (Text
"gap",Text
"\10886")
  , (Text
"gbreve",Text
"\287")
  , (Text
"gcirc",Text
"\285")
  , (Text
"gcy",Text
"\1075")
  , (Text
"gdot",Text
"\289")
  , (Text
"ge",Text
"\8805")
  , (Text
"gel",Text
"\8923")
  , (Text
"geq",Text
"\8805")
  , (Text
"geqq",Text
"\8807")
  , (Text
"geqslant",Text
"\10878")
  , (Text
"ges",Text
"\10878")
  , (Text
"gescc",Text
"\10921")
  , (Text
"gesdot",Text
"\10880")
  , (Text
"gesdoto",Text
"\10882")
  , (Text
"gesdotol",Text
"\10884")
  , (Text
"gesl",Text
"\8923\65024")
  , (Text
"gesles",Text
"\10900")
  , (Text
"gfr",Text
"\120100")
  , (Text
"gg",Text
"\8811")
  , (Text
"ggg",Text
"\8921")
  , (Text
"gimel",Text
"\8503")
  , (Text
"gjcy",Text
"\1107")
  , (Text
"gl",Text
"\8823")
  , (Text
"glE",Text
"\10898")
  , (Text
"gla",Text
"\10917")
  , (Text
"glj",Text
"\10916")
  , (Text
"gnE",Text
"\8809")
  , (Text
"gnap",Text
"\10890")
  , (Text
"gnapprox",Text
"\10890")
  , (Text
"gne",Text
"\10888")
  , (Text
"gneq",Text
"\10888")
  , (Text
"gneqq",Text
"\8809")
  , (Text
"gnsim",Text
"\8935")
  , (Text
"gopf",Text
"\120152")
  , (Text
"grave",Text
"`")
  , (Text
"gscr",Text
"\8458")
  , (Text
"gsim",Text
"\8819")
  , (Text
"gsime",Text
"\10894")
  , (Text
"gsiml",Text
"\10896")
  , (Text
"gt",Text
">")
  , (Text
"gtcc",Text
"\10919")
  , (Text
"gtcir",Text
"\10874")
  , (Text
"gtdot",Text
"\8919")
  , (Text
"gtlPar",Text
"\10645")
  , (Text
"gtquest",Text
"\10876")
  , (Text
"gtrapprox",Text
"\10886")
  , (Text
"gtrarr",Text
"\10616")
  , (Text
"gtrdot",Text
"\8919")
  , (Text
"gtreqless",Text
"\8923")
  , (Text
"gtreqqless",Text
"\10892")
  , (Text
"gtrless",Text
"\8823")
  , (Text
"gtrsim",Text
"\8819")
  , (Text
"gvertneqq",Text
"\8809\65024")
  , (Text
"gvnE",Text
"\8809\65024")
  , (Text
"hArr",Text
"\8660")
  , (Text
"hairsp",Text
"\8202")
  , (Text
"half",Text
"\189")
  , (Text
"hamilt",Text
"\8459")
  , (Text
"hardcy",Text
"\1098")
  , (Text
"harr",Text
"\8596")
  , (Text
"harrcir",Text
"\10568")
  , (Text
"harrw",Text
"\8621")
  , (Text
"hbar",Text
"\8463")
  , (Text
"hcirc",Text
"\293")
  , (Text
"hearts",Text
"\9829")
  , (Text
"heartsuit",Text
"\9829")
  , (Text
"hellip",Text
"\8230")
  , (Text
"hercon",Text
"\8889")
  , (Text
"hfr",Text
"\120101")
  , (Text
"hksearow",Text
"\10533")
  , (Text
"hkswarow",Text
"\10534")
  , (Text
"hoarr",Text
"\8703")
  , (Text
"homtht",Text
"\8763")
  , (Text
"hookleftarrow",Text
"\8617")
  , (Text
"hookrightarrow",Text
"\8618")
  , (Text
"hopf",Text
"\120153")
  , (Text
"horbar",Text
"\8213")
  , (Text
"hscr",Text
"\119997")
  , (Text
"hslash",Text
"\8463")
  , (Text
"hstrok",Text
"\295")
  , (Text
"hybull",Text
"\8259")
  , (Text
"hyphen",Text
"\8208")
  , (Text
"iacute",Text
"\237")
  , (Text
"ic",Text
"\8291")
  , (Text
"icirc",Text
"\238")
  , (Text
"icy",Text
"\1080")
  , (Text
"iecy",Text
"\1077")
  , (Text
"iexcl",Text
"\161")
  , (Text
"iff",Text
"\8660")
  , (Text
"ifr",Text
"\120102")
  , (Text
"igrave",Text
"\236")
  , (Text
"ii",Text
"\8520")
  , (Text
"iiiint",Text
"\10764")
  , (Text
"iiint",Text
"\8749")
  , (Text
"iinfin",Text
"\10716")
  , (Text
"iiota",Text
"\8489")
  , (Text
"ijlig",Text
"\307")
  , (Text
"imacr",Text
"\299")
  , (Text
"image",Text
"\8465")
  , (Text
"imagline",Text
"\8464")
  , (Text
"imagpart",Text
"\8465")
  , (Text
"imath",Text
"\305")
  , (Text
"imof",Text
"\8887")
  , (Text
"imped",Text
"\437")
  , (Text
"in",Text
"\8712")
  , (Text
"incare",Text
"\8453")
  , (Text
"infin",Text
"\8734")
  , (Text
"infintie",Text
"\10717")
  , (Text
"inodot",Text
"\305")
  , (Text
"int",Text
"\8747")
  , (Text
"intcal",Text
"\8890")
  , (Text
"integers",Text
"\8484")
  , (Text
"intercal",Text
"\8890")
  , (Text
"intlarhk",Text
"\10775")
  , (Text
"intprod",Text
"\10812")
  , (Text
"iocy",Text
"\1105")
  , (Text
"iogon",Text
"\303")
  , (Text
"iopf",Text
"\120154")
  , (Text
"iota",Text
"\953")
  , (Text
"iprod",Text
"\10812")
  , (Text
"iquest",Text
"\191")
  , (Text
"iscr",Text
"\119998")
  , (Text
"isin",Text
"\8712")
  , (Text
"isinE",Text
"\8953")
  , (Text
"isindot",Text
"\8949")
  , (Text
"isins",Text
"\8948")
  , (Text
"isinsv",Text
"\8947")
  , (Text
"isinv",Text
"\8712")
  , (Text
"it",Text
"\8290")
  , (Text
"itilde",Text
"\297")
  , (Text
"iukcy",Text
"\1110")
  , (Text
"iuml",Text
"\239")
  , (Text
"jcirc",Text
"\309")
  , (Text
"jcy",Text
"\1081")
  , (Text
"jfr",Text
"\120103")
  , (Text
"jmath",Text
"\567")
  , (Text
"jopf",Text
"\120155")
  , (Text
"jscr",Text
"\119999")
  , (Text
"jsercy",Text
"\1112")
  , (Text
"jukcy",Text
"\1108")
  , (Text
"kappa",Text
"\954")
  , (Text
"kappav",Text
"\1008")
  , (Text
"kcedil",Text
"\311")
  , (Text
"kcy",Text
"\1082")
  , (Text
"kfr",Text
"\120104")
  , (Text
"kgreen",Text
"\312")
  , (Text
"khcy",Text
"\1093")
  , (Text
"kjcy",Text
"\1116")
  , (Text
"kopf",Text
"\120156")
  , (Text
"kscr",Text
"\120000")
  , (Text
"lAarr",Text
"\8666")
  , (Text
"lArr",Text
"\8656")
  , (Text
"lAtail",Text
"\10523")
  , (Text
"lBarr",Text
"\10510")
  , (Text
"lE",Text
"\8806")
  , (Text
"lEg",Text
"\10891")
  , (Text
"lHar",Text
"\10594")
  , (Text
"lacute",Text
"\314")
  , (Text
"laemptyv",Text
"\10676")
  , (Text
"lagran",Text
"\8466")
  , (Text
"lambda",Text
"\955")
  , (Text
"lang",Text
"\10216")
  , (Text
"langd",Text
"\10641")
  , (Text
"langle",Text
"\10216")
  , (Text
"lap",Text
"\10885")
  , (Text
"laquo",Text
"\171")
  , (Text
"larr",Text
"\8592")
  , (Text
"larrb",Text
"\8676")
  , (Text
"larrbfs",Text
"\10527")
  , (Text
"larrfs",Text
"\10525")
  , (Text
"larrhk",Text
"\8617")
  , (Text
"larrlp",Text
"\8619")
  , (Text
"larrpl",Text
"\10553")
  , (Text
"larrsim",Text
"\10611")
  , (Text
"larrtl",Text
"\8610")
  , (Text
"lat",Text
"\10923")
  , (Text
"latail",Text
"\10521")
  , (Text
"late",Text
"\10925")
  , (Text
"lates",Text
"\10925\65024")
  , (Text
"lbarr",Text
"\10508")
  , (Text
"lbbrk",Text
"\10098")
  , (Text
"lbrace",Text
"{")
  , (Text
"lbrack",Text
"[")
  , (Text
"lbrke",Text
"\10635")
  , (Text
"lbrksld",Text
"\10639")
  , (Text
"lbrkslu",Text
"\10637")
  , (Text
"lcaron",Text
"\318")
  , (Text
"lcedil",Text
"\316")
  , (Text
"lceil",Text
"\8968")
  , (Text
"lcub",Text
"{")
  , (Text
"lcy",Text
"\1083")
  , (Text
"ldca",Text
"\10550")
  , (Text
"ldquo",Text
"\8220")
  , (Text
"ldquor",Text
"\8222")
  , (Text
"ldrdhar",Text
"\10599")
  , (Text
"ldrushar",Text
"\10571")
  , (Text
"ldsh",Text
"\8626")
  , (Text
"le",Text
"\8804")
  , (Text
"leftarrow",Text
"\8592")
  , (Text
"leftarrowtail",Text
"\8610")
  , (Text
"leftharpoondown",Text
"\8637")
  , (Text
"leftharpoonup",Text
"\8636")
  , (Text
"leftleftarrows",Text
"\8647")
  , (Text
"leftrightarrow",Text
"\8596")
  , (Text
"leftrightarrows",Text
"\8646")
  , (Text
"leftrightharpoons",Text
"\8651")
  , (Text
"leftrightsquigarrow",Text
"\8621")
  , (Text
"leftthreetimes",Text
"\8907")
  , (Text
"leg",Text
"\8922")
  , (Text
"leq",Text
"\8804")
  , (Text
"leqq",Text
"\8806")
  , (Text
"leqslant",Text
"\10877")
  , (Text
"les",Text
"\10877")
  , (Text
"lescc",Text
"\10920")
  , (Text
"lesdot",Text
"\10879")
  , (Text
"lesdoto",Text
"\10881")
  , (Text
"lesdotor",Text
"\10883")
  , (Text
"lesg",Text
"\8922\65024")
  , (Text
"lesges",Text
"\10899")
  , (Text
"lessapprox",Text
"\10885")
  , (Text
"lessdot",Text
"\8918")
  , (Text
"lesseqgtr",Text
"\8922")
  , (Text
"lesseqqgtr",Text
"\10891")
  , (Text
"lessgtr",Text
"\8822")
  , (Text
"lesssim",Text
"\8818")
  , (Text
"lfisht",Text
"\10620")
  , (Text
"lfloor",Text
"\8970")
  , (Text
"lfr",Text
"\120105")
  , (Text
"lg",Text
"\8822")
  , (Text
"lgE",Text
"\10897")
  , (Text
"lhard",Text
"\8637")
  , (Text
"lharu",Text
"\8636")
  , (Text
"lharul",Text
"\10602")
  , (Text
"lhblk",Text
"\9604")
  , (Text
"ljcy",Text
"\1113")
  , (Text
"ll",Text
"\8810")
  , (Text
"llarr",Text
"\8647")
  , (Text
"llcorner",Text
"\8990")
  , (Text
"llhard",Text
"\10603")
  , (Text
"lltri",Text
"\9722")
  , (Text
"lmidot",Text
"\320")
  , (Text
"lmoust",Text
"\9136")
  , (Text
"lmoustache",Text
"\9136")
  , (Text
"lnE",Text
"\8808")
  , (Text
"lnap",Text
"\10889")
  , (Text
"lnapprox",Text
"\10889")
  , (Text
"lne",Text
"\10887")
  , (Text
"lneq",Text
"\10887")
  , (Text
"lneqq",Text
"\8808")
  , (Text
"lnsim",Text
"\8934")
  , (Text
"loang",Text
"\10220")
  , (Text
"loarr",Text
"\8701")
  , (Text
"lobrk",Text
"\10214")
  , (Text
"longleftarrow",Text
"\10229")
  , (Text
"longleftrightarrow",Text
"\10231")
  , (Text
"longmapsto",Text
"\10236")
  , (Text
"longrightarrow",Text
"\10230")
  , (Text
"looparrowleft",Text
"\8619")
  , (Text
"looparrowright",Text
"\8620")
  , (Text
"lopar",Text
"\10629")
  , (Text
"lopf",Text
"\120157")
  , (Text
"loplus",Text
"\10797")
  , (Text
"lotimes",Text
"\10804")
  , (Text
"lowast",Text
"\8727")
  , (Text
"lowbar",Text
"_")
  , (Text
"loz",Text
"\9674")
  , (Text
"lozenge",Text
"\9674")
  , (Text
"lozf",Text
"\10731")
  , (Text
"lpar",Text
"(")
  , (Text
"lparlt",Text
"\10643")
  , (Text
"lrarr",Text
"\8646")
  , (Text
"lrcorner",Text
"\8991")
  , (Text
"lrhar",Text
"\8651")
  , (Text
"lrhard",Text
"\10605")
  , (Text
"lrm",Text
"\8206")
  , (Text
"lrtri",Text
"\8895")
  , (Text
"lsaquo",Text
"\8249")
  , (Text
"lscr",Text
"\120001")
  , (Text
"lsh",Text
"\8624")
  , (Text
"lsim",Text
"\8818")
  , (Text
"lsime",Text
"\10893")
  , (Text
"lsimg",Text
"\10895")
  , (Text
"lsqb",Text
"[")
  , (Text
"lsquo",Text
"\8216")
  , (Text
"lsquor",Text
"\8218")
  , (Text
"lstrok",Text
"\322")
  , (Text
"lt",Text
"<")
  , (Text
"ltcc",Text
"\10918")
  , (Text
"ltcir",Text
"\10873")
  , (Text
"ltdot",Text
"\8918")
  , (Text
"lthree",Text
"\8907")
  , (Text
"ltimes",Text
"\8905")
  , (Text
"ltlarr",Text
"\10614")
  , (Text
"ltquest",Text
"\10875")
  , (Text
"ltrPar",Text
"\10646")
  , (Text
"ltri",Text
"\9667")
  , (Text
"ltrie",Text
"\8884")
  , (Text
"ltrif",Text
"\9666")
  , (Text
"lurdshar",Text
"\10570")
  , (Text
"luruhar",Text
"\10598")
  , (Text
"lvertneqq",Text
"\8808\65024")
  , (Text
"lvnE",Text
"\8808\65024")
  , (Text
"mDDot",Text
"\8762")
  , (Text
"macr",Text
"\175")
  , (Text
"male",Text
"\9794")
  , (Text
"malt",Text
"\10016")
  , (Text
"maltese",Text
"\10016")
  , (Text
"map",Text
"\8614")
  , (Text
"mapsto",Text
"\8614")
  , (Text
"mapstodown",Text
"\8615")
  , (Text
"mapstoleft",Text
"\8612")
  , (Text
"mapstoup",Text
"\8613")
  , (Text
"marker",Text
"\9646")
  , (Text
"mcomma",Text
"\10793")
  , (Text
"mcy",Text
"\1084")
  , (Text
"mdash",Text
"\8212")
  , (Text
"measuredangle",Text
"\8737")
  , (Text
"mfr",Text
"\120106")
  , (Text
"mho",Text
"\8487")
  , (Text
"micro",Text
"\181")
  , (Text
"mid",Text
"\8739")
  , (Text
"midast",Text
"*")
  , (Text
"midcir",Text
"\10992")
  , (Text
"middot",Text
"\183")
  , (Text
"minus",Text
"\8722")
  , (Text
"minusb",Text
"\8863")
  , (Text
"minusd",Text
"\8760")
  , (Text
"minusdu",Text
"\10794")
  , (Text
"mlcp",Text
"\10971")
  , (Text
"mldr",Text
"\8230")
  , (Text
"mnplus",Text
"\8723")
  , (Text
"models",Text
"\8871")
  , (Text
"mopf",Text
"\120158")
  , (Text
"mp",Text
"\8723")
  , (Text
"mscr",Text
"\120002")
  , (Text
"mstpos",Text
"\8766")
  , (Text
"mu",Text
"\956")
  , (Text
"multimap",Text
"\8888")
  , (Text
"mumap",Text
"\8888")
  , (Text
"nGg",Text
"\8921\824")
  , (Text
"nGt",Text
"\8811\8402")
  , (Text
"nGtv",Text
"\8811\824")
  , (Text
"nLeftarrow",Text
"\8653")
  , (Text
"nLeftrightarrow",Text
"\8654")
  , (Text
"nLl",Text
"\8920\824")
  , (Text
"nLt",Text
"\8810\8402")
  , (Text
"nLtv",Text
"\8810\824")
  , (Text
"nRightarrow",Text
"\8655")
  , (Text
"nVDash",Text
"\8879")
  , (Text
"nVdash",Text
"\8878")
  , (Text
"nabla",Text
"\8711")
  , (Text
"nacute",Text
"\324")
  , (Text
"nang",Text
"\8736\8402")
  , (Text
"nap",Text
"\8777")
  , (Text
"napE",Text
"\10864\824")
  , (Text
"napid",Text
"\8779\824")
  , (Text
"napos",Text
"\329")
  , (Text
"napprox",Text
"\8777")
  , (Text
"natur",Text
"\9838")
  , (Text
"natural",Text
"\9838")
  , (Text
"naturals",Text
"\8469")
  , (Text
"nbsp",Text
"\160")
  , (Text
"nbump",Text
"\8782\824")
  , (Text
"nbumpe",Text
"\8783\824")
  , (Text
"ncap",Text
"\10819")
  , (Text
"ncaron",Text
"\328")
  , (Text
"ncedil",Text
"\326")
  , (Text
"ncong",Text
"\8775")
  , (Text
"ncongdot",Text
"\10861\824")
  , (Text
"ncup",Text
"\10818")
  , (Text
"ncy",Text
"\1085")
  , (Text
"ndash",Text
"\8211")
  , (Text
"ne",Text
"\8800")
  , (Text
"neArr",Text
"\8663")
  , (Text
"nearhk",Text
"\10532")
  , (Text
"nearr",Text
"\8599")
  , (Text
"nearrow",Text
"\8599")
  , (Text
"nedot",Text
"\8784\824")
  , (Text
"nequiv",Text
"\8802")
  , (Text
"nesear",Text
"\10536")
  , (Text
"nesim",Text
"\8770\824")
  , (Text
"nexist",Text
"\8708")
  , (Text
"nexists",Text
"\8708")
  , (Text
"nfr",Text
"\120107")
  , (Text
"ngE",Text
"\8807\824")
  , (Text
"nge",Text
"\8817")
  , (Text
"ngeq",Text
"\8817")
  , (Text
"ngeqq",Text
"\8807\824")
  , (Text
"ngeqslant",Text
"\10878\824")
  , (Text
"nges",Text
"\10878\824")
  , (Text
"ngsim",Text
"\8821")
  , (Text
"ngt",Text
"\8815")
  , (Text
"ngtr",Text
"\8815")
  , (Text
"nhArr",Text
"\8654")
  , (Text
"nharr",Text
"\8622")
  , (Text
"nhpar",Text
"\10994")
  , (Text
"ni",Text
"\8715")
  , (Text
"nis",Text
"\8956")
  , (Text
"nisd",Text
"\8954")
  , (Text
"niv",Text
"\8715")
  , (Text
"njcy",Text
"\1114")
  , (Text
"nlArr",Text
"\8653")
  , (Text
"nlE",Text
"\8806\824")
  , (Text
"nlarr",Text
"\8602")
  , (Text
"nldr",Text
"\8229")
  , (Text
"nle",Text
"\8816")
  , (Text
"nleftarrow",Text
"\8602")
  , (Text
"nleftrightarrow",Text
"\8622")
  , (Text
"nleq",Text
"\8816")
  , (Text
"nleqq",Text
"\8806\824")
  , (Text
"nleqslant",Text
"\10877\824")
  , (Text
"nles",Text
"\10877\824")
  , (Text
"nless",Text
"\8814")
  , (Text
"nlsim",Text
"\8820")
  , (Text
"nlt",Text
"\8814")
  , (Text
"nltri",Text
"\8938")
  , (Text
"nltrie",Text
"\8940")
  , (Text
"nmid",Text
"\8740")
  , (Text
"nopf",Text
"\120159")
  , (Text
"not",Text
"\172")
  , (Text
"notin",Text
"\8713")
  , (Text
"notinE",Text
"\8953\824")
  , (Text
"notindot",Text
"\8949\824")
  , (Text
"notinva",Text
"\8713")
  , (Text
"notinvb",Text
"\8951")
  , (Text
"notinvc",Text
"\8950")
  , (Text
"notni",Text
"\8716")
  , (Text
"notniva",Text
"\8716")
  , (Text
"notnivb",Text
"\8958")
  , (Text
"notnivc",Text
"\8957")
  , (Text
"npar",Text
"\8742")
  , (Text
"nparallel",Text
"\8742")
  , (Text
"nparsl",Text
"\11005\8421")
  , (Text
"npart",Text
"\8706\824")
  , (Text
"npolint",Text
"\10772")
  , (Text
"npr",Text
"\8832")
  , (Text
"nprcue",Text
"\8928")
  , (Text
"npre",Text
"\10927\824")
  , (Text
"nprec",Text
"\8832")
  , (Text
"npreceq",Text
"\10927\824")
  , (Text
"nrArr",Text
"\8655")
  , (Text
"nrarr",Text
"\8603")
  , (Text
"nrarrc",Text
"\10547\824")
  , (Text
"nrarrw",Text
"\8605\824")
  , (Text
"nrightarrow",Text
"\8603")
  , (Text
"nrtri",Text
"\8939")
  , (Text
"nrtrie",Text
"\8941")
  , (Text
"nsc",Text
"\8833")
  , (Text
"nsccue",Text
"\8929")
  , (Text
"nsce",Text
"\10928\824")
  , (Text
"nscr",Text
"\120003")
  , (Text
"nshortmid",Text
"\8740")
  , (Text
"nshortparallel",Text
"\8742")
  , (Text
"nsim",Text
"\8769")
  , (Text
"nsime",Text
"\8772")
  , (Text
"nsimeq",Text
"\8772")
  , (Text
"nsmid",Text
"\8740")
  , (Text
"nspar",Text
"\8742")
  , (Text
"nsqsube",Text
"\8930")
  , (Text
"nsqsupe",Text
"\8931")
  , (Text
"nsub",Text
"\8836")
  , (Text
"nsubE",Text
"\10949\824")
  , (Text
"nsube",Text
"\8840")
  , (Text
"nsubset",Text
"\8834\8402")
  , (Text
"nsubseteq",Text
"\8840")
  , (Text
"nsubseteqq",Text
"\10949\824")
  , (Text
"nsucc",Text
"\8833")
  , (Text
"nsucceq",Text
"\10928\824")
  , (Text
"nsup",Text
"\8837")
  , (Text
"nsupE",Text
"\10950\824")
  , (Text
"nsupe",Text
"\8841")
  , (Text
"nsupset",Text
"\8835\8402")
  , (Text
"nsupseteq",Text
"\8841")
  , (Text
"nsupseteqq",Text
"\10950\824")
  , (Text
"ntgl",Text
"\8825")
  , (Text
"ntilde",Text
"\241")
  , (Text
"ntlg",Text
"\8824")
  , (Text
"ntriangleleft",Text
"\8938")
  , (Text
"ntrianglelefteq",Text
"\8940")
  , (Text
"ntriangleright",Text
"\8939")
  , (Text
"ntrianglerighteq",Text
"\8941")
  , (Text
"nu",Text
"\957")
  , (Text
"num",Text
"#")
  , (Text
"numero",Text
"\8470")
  , (Text
"numsp",Text
"\8199")
  , (Text
"nvDash",Text
"\8877")
  , (Text
"nvHarr",Text
"\10500")
  , (Text
"nvap",Text
"\8781\8402")
  , (Text
"nvdash",Text
"\8876")
  , (Text
"nvge",Text
"\8805\8402")
  , (Text
"nvgt",Text
">\8402")
  , (Text
"nvinfin",Text
"\10718")
  , (Text
"nvlArr",Text
"\10498")
  , (Text
"nvle",Text
"\8804\8402")
  , (Text
"nvlt",Text
"<\8402")
  , (Text
"nvltrie",Text
"\8884\8402")
  , (Text
"nvrArr",Text
"\10499")
  , (Text
"nvrtrie",Text
"\8885\8402")
  , (Text
"nvsim",Text
"\8764\8402")
  , (Text
"nwArr",Text
"\8662")
  , (Text
"nwarhk",Text
"\10531")
  , (Text
"nwarr",Text
"\8598")
  , (Text
"nwarrow",Text
"\8598")
  , (Text
"nwnear",Text
"\10535")
  , (Text
"oS",Text
"\9416")
  , (Text
"oacute",Text
"\243")
  , (Text
"oast",Text
"\8859")
  , (Text
"ocir",Text
"\8858")
  , (Text
"ocirc",Text
"\244")
  , (Text
"ocy",Text
"\1086")
  , (Text
"odash",Text
"\8861")
  , (Text
"odblac",Text
"\337")
  , (Text
"odiv",Text
"\10808")
  , (Text
"odot",Text
"\8857")
  , (Text
"odsold",Text
"\10684")
  , (Text
"oelig",Text
"\339")
  , (Text
"ofcir",Text
"\10687")
  , (Text
"ofr",Text
"\120108")
  , (Text
"ogon",Text
"\731")
  , (Text
"ograve",Text
"\242")
  , (Text
"ogt",Text
"\10689")
  , (Text
"ohbar",Text
"\10677")
  , (Text
"ohm",Text
"\937")
  , (Text
"oint",Text
"\8750")
  , (Text
"olarr",Text
"\8634")
  , (Text
"olcir",Text
"\10686")
  , (Text
"olcross",Text
"\10683")
  , (Text
"oline",Text
"\8254")
  , (Text
"olt",Text
"\10688")
  , (Text
"omacr",Text
"\333")
  , (Text
"omega",Text
"\969")
  , (Text
"omicron",Text
"\959")
  , (Text
"omid",Text
"\10678")
  , (Text
"ominus",Text
"\8854")
  , (Text
"oopf",Text
"\120160")
  , (Text
"opar",Text
"\10679")
  , (Text
"operp",Text
"\10681")
  , (Text
"oplus",Text
"\8853")
  , (Text
"or",Text
"\8744")
  , (Text
"orarr",Text
"\8635")
  , (Text
"ord",Text
"\10845")
  , (Text
"order",Text
"\8500")
  , (Text
"orderof",Text
"\8500")
  , (Text
"ordf",Text
"\170")
  , (Text
"ordm",Text
"\186")
  , (Text
"origof",Text
"\8886")
  , (Text
"oror",Text
"\10838")
  , (Text
"orslope",Text
"\10839")
  , (Text
"orv",Text
"\10843")
  , (Text
"oscr",Text
"\8500")
  , (Text
"oslash",Text
"\248")
  , (Text
"osol",Text
"\8856")
  , (Text
"otilde",Text
"\245")
  , (Text
"otimes",Text
"\8855")
  , (Text
"otimesas",Text
"\10806")
  , (Text
"ouml",Text
"\246")
  , (Text
"ovbar",Text
"\9021")
  , (Text
"par",Text
"\8741")
  , (Text
"para",Text
"\182")
  , (Text
"parallel",Text
"\8741")
  , (Text
"parsim",Text
"\10995")
  , (Text
"parsl",Text
"\11005")
  , (Text
"part",Text
"\8706")
  , (Text
"pcy",Text
"\1087")
  , (Text
"percnt",Text
"%")
  , (Text
"period",Text
".")
  , (Text
"permil",Text
"\8240")
  , (Text
"perp",Text
"\8869")
  , (Text
"pertenk",Text
"\8241")
  , (Text
"pfr",Text
"\120109")
  , (Text
"phi",Text
"\966")
  , (Text
"phiv",Text
"\981")
  , (Text
"phmmat",Text
"\8499")
  , (Text
"phone",Text
"\9742")
  , (Text
"pi",Text
"\960")
  , (Text
"pitchfork",Text
"\8916")
  , (Text
"piv",Text
"\982")
  , (Text
"planck",Text
"\8463")
  , (Text
"planckh",Text
"\8462")
  , (Text
"plankv",Text
"\8463")
  , (Text
"plus",Text
"+")
  , (Text
"plusacir",Text
"\10787")
  , (Text
"plusb",Text
"\8862")
  , (Text
"pluscir",Text
"\10786")
  , (Text
"plusdo",Text
"\8724")
  , (Text
"plusdu",Text
"\10789")
  , (Text
"pluse",Text
"\10866")
  , (Text
"plusmn",Text
"\177")
  , (Text
"plussim",Text
"\10790")
  , (Text
"plustwo",Text
"\10791")
  , (Text
"pm",Text
"\177")
  , (Text
"pointint",Text
"\10773")
  , (Text
"popf",Text
"\120161")
  , (Text
"pound",Text
"\163")
  , (Text
"pr",Text
"\8826")
  , (Text
"prE",Text
"\10931")
  , (Text
"prap",Text
"\10935")
  , (Text
"prcue",Text
"\8828")
  , (Text
"pre",Text
"\10927")
  , (Text
"prec",Text
"\8826")
  , (Text
"precapprox",Text
"\10935")
  , (Text
"preccurlyeq",Text
"\8828")
  , (Text
"preceq",Text
"\10927")
  , (Text
"precnapprox",Text
"\10937")
  , (Text
"precneqq",Text
"\10933")
  , (Text
"precnsim",Text
"\8936")
  , (Text
"precsim",Text
"\8830")
  , (Text
"prime",Text
"\8242")
  , (Text
"primes",Text
"\8473")
  , (Text
"prnE",Text
"\10933")
  , (Text
"prnap",Text
"\10937")
  , (Text
"prnsim",Text
"\8936")
  , (Text
"prod",Text
"\8719")
  , (Text
"profalar",Text
"\9006")
  , (Text
"profline",Text
"\8978")
  , (Text
"profsurf",Text
"\8979")
  , (Text
"prop",Text
"\8733")
  , (Text
"propto",Text
"\8733")
  , (Text
"prsim",Text
"\8830")
  , (Text
"prurel",Text
"\8880")
  , (Text
"pscr",Text
"\120005")
  , (Text
"psi",Text
"\968")
  , (Text
"puncsp",Text
"\8200")
  , (Text
"qfr",Text
"\120110")
  , (Text
"qint",Text
"\10764")
  , (Text
"qopf",Text
"\120162")
  , (Text
"qprime",Text
"\8279")
  , (Text
"qscr",Text
"\120006")
  , (Text
"quaternions",Text
"\8461")
  , (Text
"quatint",Text
"\10774")
  , (Text
"quest",Text
"?")
  , (Text
"questeq",Text
"\8799")
  , (Text
"quot",Text
"\"")
  , (Text
"rAarr",Text
"\8667")
  , (Text
"rArr",Text
"\8658")
  , (Text
"rAtail",Text
"\10524")
  , (Text
"rBarr",Text
"\10511")
  , (Text
"rHar",Text
"\10596")
  , (Text
"race",Text
"\8765\817")
  , (Text
"racute",Text
"\341")
  , (Text
"radic",Text
"\8730")
  , (Text
"raemptyv",Text
"\10675")
  , (Text
"rang",Text
"\10217")
  , (Text
"rangd",Text
"\10642")
  , (Text
"range",Text
"\10661")
  , (Text
"rangle",Text
"\10217")
  , (Text
"raquo",Text
"\187")
  , (Text
"rarr",Text
"\8594")
  , (Text
"rarrap",Text
"\10613")
  , (Text
"rarrb",Text
"\8677")
  , (Text
"rarrbfs",Text
"\10528")
  , (Text
"rarrc",Text
"\10547")
  , (Text
"rarrfs",Text
"\10526")
  , (Text
"rarrhk",Text
"\8618")
  , (Text
"rarrlp",Text
"\8620")
  , (Text
"rarrpl",Text
"\10565")
  , (Text
"rarrsim",Text
"\10612")
  , (Text
"rarrtl",Text
"\8611")
  , (Text
"rarrw",Text
"\8605")
  , (Text
"ratail",Text
"\10522")
  , (Text
"ratio",Text
"\8758")
  , (Text
"rationals",Text
"\8474")
  , (Text
"rbarr",Text
"\10509")
  , (Text
"rbbrk",Text
"\10099")
  , (Text
"rbrace",Text
"}")
  , (Text
"rbrack",Text
"]")
  , (Text
"rbrke",Text
"\10636")
  , (Text
"rbrksld",Text
"\10638")
  , (Text
"rbrkslu",Text
"\10640")
  , (Text
"rcaron",Text
"\345")
  , (Text
"rcedil",Text
"\343")
  , (Text
"rceil",Text
"\8969")
  , (Text
"rcub",Text
"}")
  , (Text
"rcy",Text
"\1088")
  , (Text
"rdca",Text
"\10551")
  , (Text
"rdldhar",Text
"\10601")
  , (Text
"rdquo",Text
"\8221")
  , (Text
"rdquor",Text
"\8221")
  , (Text
"rdsh",Text
"\8627")
  , (Text
"real",Text
"\8476")
  , (Text
"realine",Text
"\8475")
  , (Text
"realpart",Text
"\8476")
  , (Text
"reals",Text
"\8477")
  , (Text
"rect",Text
"\9645")
  , (Text
"reg",Text
"\174")
  , (Text
"rfisht",Text
"\10621")
  , (Text
"rfloor",Text
"\8971")
  , (Text
"rfr",Text
"\120111")
  , (Text
"rhard",Text
"\8641")
  , (Text
"rharu",Text
"\8640")
  , (Text
"rharul",Text
"\10604")
  , (Text
"rho",Text
"\961")
  , (Text
"rhov",Text
"\1009")
  , (Text
"rightarrow",Text
"\8594")
  , (Text
"rightarrowtail",Text
"\8611")
  , (Text
"rightharpoondown",Text
"\8641")
  , (Text
"rightharpoonup",Text
"\8640")
  , (Text
"rightleftarrows",Text
"\8644")
  , (Text
"rightleftharpoons",Text
"\8652")
  , (Text
"rightrightarrows",Text
"\8649")
  , (Text
"rightsquigarrow",Text
"\8605")
  , (Text
"rightthreetimes",Text
"\8908")
  , (Text
"ring",Text
"\730")
  , (Text
"risingdotseq",Text
"\8787")
  , (Text
"rlarr",Text
"\8644")
  , (Text
"rlhar",Text
"\8652")
  , (Text
"rlm",Text
"\8207")
  , (Text
"rmoust",Text
"\9137")
  , (Text
"rmoustache",Text
"\9137")
  , (Text
"rnmid",Text
"\10990")
  , (Text
"roang",Text
"\10221")
  , (Text
"roarr",Text
"\8702")
  , (Text
"robrk",Text
"\10215")
  , (Text
"ropar",Text
"\10630")
  , (Text
"ropf",Text
"\120163")
  , (Text
"roplus",Text
"\10798")
  , (Text
"rotimes",Text
"\10805")
  , (Text
"rpar",Text
")")
  , (Text
"rpargt",Text
"\10644")
  , (Text
"rppolint",Text
"\10770")
  , (Text
"rrarr",Text
"\8649")
  , (Text
"rsaquo",Text
"\8250")
  , (Text
"rscr",Text
"\120007")
  , (Text
"rsh",Text
"\8625")
  , (Text
"rsqb",Text
"]")
  , (Text
"rsquo",Text
"\8217")
  , (Text
"rsquor",Text
"\8217")
  , (Text
"rthree",Text
"\8908")
  , (Text
"rtimes",Text
"\8906")
  , (Text
"rtri",Text
"\9657")
  , (Text
"rtrie",Text
"\8885")
  , (Text
"rtrif",Text
"\9656")
  , (Text
"rtriltri",Text
"\10702")
  , (Text
"ruluhar",Text
"\10600")
  , (Text
"rx",Text
"\8478")
  , (Text
"sacute",Text
"\347")
  , (Text
"sbquo",Text
"\8218")
  , (Text
"sc",Text
"\8827")
  , (Text
"scE",Text
"\10932")
  , (Text
"scap",Text
"\10936")
  , (Text
"scaron",Text
"\353")
  , (Text
"sccue",Text
"\8829")
  , (Text
"sce",Text
"\10928")
  , (Text
"scedil",Text
"\351")
  , (Text
"scirc",Text
"\349")
  , (Text
"scnE",Text
"\10934")
  , (Text
"scnap",Text
"\10938")
  , (Text
"scnsim",Text
"\8937")
  , (Text
"scpolint",Text
"\10771")
  , (Text
"scsim",Text
"\8831")
  , (Text
"scy",Text
"\1089")
  , (Text
"sdot",Text
"\8901")
  , (Text
"sdotb",Text
"\8865")
  , (Text
"sdote",Text
"\10854")
  , (Text
"seArr",Text
"\8664")
  , (Text
"searhk",Text
"\10533")
  , (Text
"searr",Text
"\8600")
  , (Text
"searrow",Text
"\8600")
  , (Text
"sect",Text
"\167")
  , (Text
"semi",Text
";")
  , (Text
"seswar",Text
"\10537")
  , (Text
"setminus",Text
"\8726")
  , (Text
"setmn",Text
"\8726")
  , (Text
"sext",Text
"\10038")
  , (Text
"sfr",Text
"\120112")
  , (Text
"sfrown",Text
"\8994")
  , (Text
"sharp",Text
"\9839")
  , (Text
"shchcy",Text
"\1097")
  , (Text
"shcy",Text
"\1096")
  , (Text
"shortmid",Text
"\8739")
  , (Text
"shortparallel",Text
"\8741")
  , (Text
"shy",Text
"\173")
  , (Text
"sigma",Text
"\963")
  , (Text
"sigmaf",Text
"\962")
  , (Text
"sigmav",Text
"\962")
  , (Text
"sim",Text
"\8764")
  , (Text
"simdot",Text
"\10858")
  , (Text
"sime",Text
"\8771")
  , (Text
"simeq",Text
"\8771")
  , (Text
"simg",Text
"\10910")
  , (Text
"simgE",Text
"\10912")
  , (Text
"siml",Text
"\10909")
  , (Text
"simlE",Text
"\10911")
  , (Text
"simne",Text
"\8774")
  , (Text
"simplus",Text
"\10788")
  , (Text
"simrarr",Text
"\10610")
  , (Text
"slarr",Text
"\8592")
  , (Text
"smallsetminus",Text
"\8726")
  , (Text
"smashp",Text
"\10803")
  , (Text
"smeparsl",Text
"\10724")
  , (Text
"smid",Text
"\8739")
  , (Text
"smile",Text
"\8995")
  , (Text
"smt",Text
"\10922")
  , (Text
"smte",Text
"\10924")
  , (Text
"smtes",Text
"\10924\65024")
  , (Text
"softcy",Text
"\1100")
  , (Text
"sol",Text
"/")
  , (Text
"solb",Text
"\10692")
  , (Text
"solbar",Text
"\9023")
  , (Text
"sopf",Text
"\120164")
  , (Text
"spades",Text
"\9824")
  , (Text
"spadesuit",Text
"\9824")
  , (Text
"spar",Text
"\8741")
  , (Text
"sqcap",Text
"\8851")
  , (Text
"sqcaps",Text
"\8851\65024")
  , (Text
"sqcup",Text
"\8852")
  , (Text
"sqcups",Text
"\8852\65024")
  , (Text
"sqsub",Text
"\8847")
  , (Text
"sqsube",Text
"\8849")
  , (Text
"sqsubset",Text
"\8847")
  , (Text
"sqsubseteq",Text
"\8849")
  , (Text
"sqsup",Text
"\8848")
  , (Text
"sqsupe",Text
"\8850")
  , (Text
"sqsupset",Text
"\8848")
  , (Text
"sqsupseteq",Text
"\8850")
  , (Text
"squ",Text
"\9633")
  , (Text
"square",Text
"\9633")
  , (Text
"squarf",Text
"\9642")
  , (Text
"squf",Text
"\9642")
  , (Text
"srarr",Text
"\8594")
  , (Text
"sscr",Text
"\120008")
  , (Text
"ssetmn",Text
"\8726")
  , (Text
"ssmile",Text
"\8995")
  , (Text
"sstarf",Text
"\8902")
  , (Text
"star",Text
"\9734")
  , (Text
"starf",Text
"\9733")
  , (Text
"straightepsilon",Text
"\1013")
  , (Text
"straightphi",Text
"\981")
  , (Text
"strns",Text
"\175")
  , (Text
"sub",Text
"\8834")
  , (Text
"subE",Text
"\10949")
  , (Text
"subdot",Text
"\10941")
  , (Text
"sube",Text
"\8838")
  , (Text
"subedot",Text
"\10947")
  , (Text
"submult",Text
"\10945")
  , (Text
"subnE",Text
"\10955")
  , (Text
"subne",Text
"\8842")
  , (Text
"subplus",Text
"\10943")
  , (Text
"subrarr",Text
"\10617")
  , (Text
"subset",Text
"\8834")
  , (Text
"subseteq",Text
"\8838")
  , (Text
"subseteqq",Text
"\10949")
  , (Text
"subsetneq",Text
"\8842")
  , (Text
"subsetneqq",Text
"\10955")
  , (Text
"subsim",Text
"\10951")
  , (Text
"subsub",Text
"\10965")
  , (Text
"subsup",Text
"\10963")
  , (Text
"succ",Text
"\8827")
  , (Text
"succapprox",Text
"\10936")
  , (Text
"succcurlyeq",Text
"\8829")
  , (Text
"succeq",Text
"\10928")
  , (Text
"succnapprox",Text
"\10938")
  , (Text
"succneqq",Text
"\10934")
  , (Text
"succnsim",Text
"\8937")
  , (Text
"succsim",Text
"\8831")
  , (Text
"sum",Text
"\8721")
  , (Text
"sung",Text
"\9834")
  , (Text
"sup",Text
"\8835")
  , (Text
"sup1",Text
"\185")
  , (Text
"sup2",Text
"\178")
  , (Text
"sup3",Text
"\179")
  , (Text
"supE",Text
"\10950")
  , (Text
"supdot",Text
"\10942")
  , (Text
"supdsub",Text
"\10968")
  , (Text
"supe",Text
"\8839")
  , (Text
"supedot",Text
"\10948")
  , (Text
"suphsol",Text
"\10185")
  , (Text
"suphsub",Text
"\10967")
  , (Text
"suplarr",Text
"\10619")
  , (Text
"supmult",Text
"\10946")
  , (Text
"supnE",Text
"\10956")
  , (Text
"supne",Text
"\8843")
  , (Text
"supplus",Text
"\10944")
  , (Text
"supset",Text
"\8835")
  , (Text
"supseteq",Text
"\8839")
  , (Text
"supseteqq",Text
"\10950")
  , (Text
"supsetneq",Text
"\8843")
  , (Text
"supsetneqq",Text
"\10956")
  , (Text
"supsim",Text
"\10952")
  , (Text
"supsub",Text
"\10964")
  , (Text
"supsup",Text
"\10966")
  , (Text
"swArr",Text
"\8665")
  , (Text
"swarhk",Text
"\10534")
  , (Text
"swarr",Text
"\8601")
  , (Text
"swarrow",Text
"\8601")
  , (Text
"swnwar",Text
"\10538")
  , (Text
"szlig",Text
"\223")
  , (Text
"target",Text
"\8982")
  , (Text
"tau",Text
"\964")
  , (Text
"tbrk",Text
"\9140")
  , (Text
"tcaron",Text
"\357")
  , (Text
"tcedil",Text
"\355")
  , (Text
"tcy",Text
"\1090")
  , (Text
"tdot",Text
" \8411")
  , (Text
"telrec",Text
"\8981")
  , (Text
"tfr",Text
"\120113")
  , (Text
"there4",Text
"\8756")
  , (Text
"therefore",Text
"\8756")
  , (Text
"theta",Text
"\952")
  , (Text
"thetasym",Text
"\977")
  , (Text
"thetav",Text
"\977")
  , (Text
"thickapprox",Text
"\8776")
  , (Text
"thicksim",Text
"\8764")
  , (Text
"thinsp",Text
"\8201")
  , (Text
"thkap",Text
"\8776")
  , (Text
"thksim",Text
"\8764")
  , (Text
"thorn",Text
"\254")
  , (Text
"tilde",Text
"\732")
  , (Text
"times",Text
"\215")
  , (Text
"timesb",Text
"\8864")
  , (Text
"timesbar",Text
"\10801")
  , (Text
"timesd",Text
"\10800")
  , (Text
"tint",Text
"\8749")
  , (Text
"toea",Text
"\10536")
  , (Text
"top",Text
"\8868")
  , (Text
"topbot",Text
"\9014")
  , (Text
"topcir",Text
"\10993")
  , (Text
"topf",Text
"\120165")
  , (Text
"topfork",Text
"\10970")
  , (Text
"tosa",Text
"\10537")
  , (Text
"tprime",Text
"\8244")
  , (Text
"trade",Text
"\8482")
  , (Text
"triangle",Text
"\9653")
  , (Text
"triangledown",Text
"\9663")
  , (Text
"triangleleft",Text
"\9667")
  , (Text
"trianglelefteq",Text
"\8884")
  , (Text
"triangleq",Text
"\8796")
  , (Text
"triangleright",Text
"\9657")
  , (Text
"trianglerighteq",Text
"\8885")
  , (Text
"tridot",Text
"\9708")
  , (Text
"trie",Text
"\8796")
  , (Text
"triminus",Text
"\10810")
  , (Text
"triplus",Text
"\10809")
  , (Text
"trisb",Text
"\10701")
  , (Text
"tritime",Text
"\10811")
  , (Text
"trpezium",Text
"\9186")
  , (Text
"tscr",Text
"\120009")
  , (Text
"tscy",Text
"\1094")
  , (Text
"tshcy",Text
"\1115")
  , (Text
"tstrok",Text
"\359")
  , (Text
"twixt",Text
"\8812")
  , (Text
"twoheadleftarrow",Text
"\8606")
  , (Text
"twoheadrightarrow",Text
"\8608")
  , (Text
"uArr",Text
"\8657")
  , (Text
"uHar",Text
"\10595")
  , (Text
"uacute",Text
"\250")
  , (Text
"uarr",Text
"\8593")
  , (Text
"ubrcy",Text
"\1118")
  , (Text
"ubreve",Text
"\365")
  , (Text
"ucirc",Text
"\251")
  , (Text
"ucy",Text
"\1091")
  , (Text
"udarr",Text
"\8645")
  , (Text
"udblac",Text
"\369")
  , (Text
"udhar",Text
"\10606")
  , (Text
"ufisht",Text
"\10622")
  , (Text
"ufr",Text
"\120114")
  , (Text
"ugrave",Text
"\249")
  , (Text
"uharl",Text
"\8639")
  , (Text
"uharr",Text
"\8638")
  , (Text
"uhblk",Text
"\9600")
  , (Text
"ulcorn",Text
"\8988")
  , (Text
"ulcorner",Text
"\8988")
  , (Text
"ulcrop",Text
"\8975")
  , (Text
"ultri",Text
"\9720")
  , (Text
"umacr",Text
"\363")
  , (Text
"uml",Text
"\168")
  , (Text
"uogon",Text
"\371")
  , (Text
"uopf",Text
"\120166")
  , (Text
"uparrow",Text
"\8593")
  , (Text
"updownarrow",Text
"\8597")
  , (Text
"upharpoonleft",Text
"\8639")
  , (Text
"upharpoonright",Text
"\8638")
  , (Text
"uplus",Text
"\8846")
  , (Text
"upsi",Text
"\965")
  , (Text
"upsih",Text
"\978")
  , (Text
"upsilon",Text
"\965")
  , (Text
"upuparrows",Text
"\8648")
  , (Text
"urcorn",Text
"\8989")
  , (Text
"urcorner",Text
"\8989")
  , (Text
"urcrop",Text
"\8974")
  , (Text
"uring",Text
"\367")
  , (Text
"urtri",Text
"\9721")
  , (Text
"uscr",Text
"\120010")
  , (Text
"utdot",Text
"\8944")
  , (Text
"utilde",Text
"\361")
  , (Text
"utri",Text
"\9653")
  , (Text
"utrif",Text
"\9652")
  , (Text
"uuarr",Text
"\8648")
  , (Text
"uuml",Text
"\252")
  , (Text
"uwangle",Text
"\10663")
  , (Text
"vArr",Text
"\8661")
  , (Text
"vBar",Text
"\10984")
  , (Text
"vBarv",Text
"\10985")
  , (Text
"vDash",Text
"\8872")
  , (Text
"vangrt",Text
"\10652")
  , (Text
"varepsilon",Text
"\949")
  , (Text
"varkappa",Text
"\1008")
  , (Text
"varnothing",Text
"\8709")
  , (Text
"varphi",Text
"\981")
  , (Text
"varpi",Text
"\982")
  , (Text
"varpropto",Text
"\8733")
  , (Text
"varr",Text
"\8597")
  , (Text
"varrho",Text
"\1009")
  , (Text
"varsigma",Text
"\962")
  , (Text
"varsubsetneq",Text
"\8842\65024")
  , (Text
"varsubsetneqq",Text
"\10955\65024")
  , (Text
"varsupsetneq",Text
"\8843\65024")
  , (Text
"varsupsetneqq",Text
"\10956\65024")
  , (Text
"vartheta",Text
"\977")
  , (Text
"vartriangleleft",Text
"\8882")
  , (Text
"vartriangleright",Text
"\8883")
  , (Text
"vcy",Text
"\1074")
  , (Text
"vdash",Text
"\8866")
  , (Text
"vee",Text
"\8744")
  , (Text
"veebar",Text
"\8891")
  , (Text
"veeeq",Text
"\8794")
  , (Text
"vellip",Text
"\8942")
  , (Text
"verbar",Text
"|")
  , (Text
"vert",Text
"|")
  , (Text
"vfr",Text
"\120115")
  , (Text
"vltri",Text
"\8882")
  , (Text
"vnsub",Text
"\8834\8402")
  , (Text
"vnsup",Text
"\8835\8402")
  , (Text
"vopf",Text
"\120167")
  , (Text
"vprop",Text
"\8733")
  , (Text
"vrtri",Text
"\8883")
  , (Text
"vscr",Text
"\120011")
  , (Text
"vsubnE",Text
"\10955\65024")
  , (Text
"vsubne",Text
"\8842\65024")
  , (Text
"vsupnE",Text
"\10956\65024")
  , (Text
"vsupne",Text
"\8843\65024")
  , (Text
"vzigzag",Text
"\10650")
  , (Text
"wcirc",Text
"\373")
  , (Text
"wedbar",Text
"\10847")
  , (Text
"wedge",Text
"\8743")
  , (Text
"wedgeq",Text
"\8793")
  , (Text
"weierp",Text
"\8472")
  , (Text
"wfr",Text
"\120116")
  , (Text
"wopf",Text
"\120168")
  , (Text
"wp",Text
"\8472")
  , (Text
"wr",Text
"\8768")
  , (Text
"wreath",Text
"\8768")
  , (Text
"wscr",Text
"\120012")
  , (Text
"xcap",Text
"\8898")
  , (Text
"xcirc",Text
"\9711")
  , (Text
"xcup",Text
"\8899")
  , (Text
"xdtri",Text
"\9661")
  , (Text
"xfr",Text
"\120117")
  , (Text
"xhArr",Text
"\10234")
  , (Text
"xharr",Text
"\10231")
  , (Text
"xi",Text
"\958")
  , (Text
"xlArr",Text
"\10232")
  , (Text
"xlarr",Text
"\10229")
  , (Text
"xmap",Text
"\10236")
  , (Text
"xnis",Text
"\8955")
  , (Text
"xodot",Text
"\10752")
  , (Text
"xopf",Text
"\120169")
  , (Text
"xoplus",Text
"\10753")
  , (Text
"xotime",Text
"\10754")
  , (Text
"xrArr",Text
"\10233")
  , (Text
"xrarr",Text
"\10230")
  , (Text
"xscr",Text
"\120013")
  , (Text
"xsqcup",Text
"\10758")
  , (Text
"xuplus",Text
"\10756")
  , (Text
"xutri",Text
"\9651")
  , (Text
"xvee",Text
"\8897")
  , (Text
"xwedge",Text
"\8896")
  , (Text
"yacute",Text
"\253")
  , (Text
"yacy",Text
"\1103")
  , (Text
"ycirc",Text
"\375")
  , (Text
"ycy",Text
"\1099")
  , (Text
"yen",Text
"\165")
  , (Text
"yfr",Text
"\120118")
  , (Text
"yicy",Text
"\1111")
  , (Text
"yopf",Text
"\120170")
  , (Text
"yscr",Text
"\120014")
  , (Text
"yucy",Text
"\1102")
  , (Text
"yuml",Text
"\255")
  , (Text
"zacute",Text
"\378")
  , (Text
"zcaron",Text
"\382")
  , (Text
"zcy",Text
"\1079")
  , (Text
"zdot",Text
"\380")
  , (Text
"zeetrf",Text
"\8488")
  , (Text
"zeta",Text
"\950")
  , (Text
"zfr",Text
"\120119")
  , (Text
"zhcy",Text
"\1078")
  , (Text
"zigrarr",Text
"\8669")
  , (Text
"zopf",Text
"\120171")
  , (Text
"zscr",Text
"\120015")
  , (Text
"zwj",Text
"\8205")
  , (Text
"zwnj",Text
"\8204")]