{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- | Matches and extracts entities from byte strings.
module Zenacy.HTML.Internal.Entity
  ( entityMatch
  , entityTrie
  , entityData
  ) where

import Zenacy.HTML.Internal.BS
import Zenacy.HTML.Internal.Char
import Data.Char
  ( chr
  , ord
  )
import qualified Data.Text as Text
  ( pack
  )
import qualified Data.Text.Encoding as Text
  ( encodeUtf8
  )
import Zenacy.HTML.Internal.Trie
  ( Trie
  )
import qualified Zenacy.HTML.Internal.Trie as Trie
  ( fromList
  , match
  )
import Data.Word
  ( Word8
  )

-- | Searches for an entity match.
-- Returns a tuple with the prefix, its value, and the remaining string.
entityMatch :: BS -> Maybe (BS, BS, BS)
entityMatch :: BS -> Maybe (BS, BS, BS)
entityMatch = Trie BS -> BS -> Maybe (BS, BS, BS)
forall a. Trie a -> BS -> Maybe (BS, a, BS)
Trie.match Trie BS
entityTrie

-- | A trie of the entity data with surrogates converted.
entityTrie :: Trie BS
entityTrie :: Trie BS
entityTrie =
  [(BS, BS)] -> Trie BS
forall a. [(BS, a)] -> Trie a
Trie.fromList ([(BS, BS)] -> Trie BS) -> [(BS, BS)] -> Trie BS
forall a b. (a -> b) -> a -> b
$ ((BS, [Char]) -> (BS, BS)) -> [(BS, [Char])] -> [(BS, BS)]
forall a b. (a -> b) -> [a] -> [b]
map ((BS, [Char]) -> (BS, BS)
forall a. (a, [Char]) -> (a, BS)
f ((BS, [Char]) -> (BS, BS))
-> ((BS, [Char]) -> (BS, [Char])) -> (BS, [Char]) -> (BS, BS)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BS, [Char]) -> (BS, [Char])
forall a. (a, [Char]) -> (a, [Char])
g) [(BS, [Char])]
entityData
  where
    f :: (a, [Char]) -> (a, BS)
f (a
x, [Char]
y) = (a
x, Text -> BS
Text.encodeUtf8 (Text -> BS) -> Text -> BS
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
Text.pack [Char]
y)
    g :: (a, [Char]) -> (a, [Char])
g (a
x, [Char]
y) = case [Char]
y of
      [Char
a, Char
b] ->
        let a' :: Int
a' = Char -> Int
ord Char
a
            b' :: Int
b' = Char -> Int
ord Char
b
        in if Int -> Int -> Bool
isUTF16Surrogate Int
a' Int
b'
              then (a
x, [Int -> Int -> Char
convUTF16Surrogate Int
a' Int
b'])
              else (a
x, [Char
a,Char
b])
      [Char]
_otherwise ->
        (a
x, [Char]
y)

-- | Converts a surrogate pair to a unicode character.
convUTF16Surrogate :: Int -> Int -> Char
convUTF16Surrogate :: Int -> Int -> Char
convUTF16Surrogate Int
high Int
low =
  Int -> Char
chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ (Int
high Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
0xD800) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
0x400 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
low Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
0xDC00) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0x10000

-- | Determines is a pair of codes represent a surrogate.
isUTF16Surrogate :: Int -> Int -> Bool
isUTF16Surrogate :: Int -> Int -> Bool
isUTF16Surrogate Int
high Int
low =
  Int
high Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0xD800 Bool -> Bool -> Bool
&& Int
high Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0xDBFF Bool -> Bool -> Bool
&& Int
low Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0xDC00 Bool -> Bool -> Bool
&& Int
low Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0xDFFF

-- | The raw entity data.
entityData :: [(BS,String)]
entityData :: [(BS, [Char])]
entityData =
  [(BS
"Aacute",[Char]
"\x00C1")
  ,(BS
"aacute",[Char]
"\x00E1")
  ,(BS
"Aacute;",[Char]
"\x00C1")
  ,(BS
"aacute;",[Char]
"\x00E1")
  ,(BS
"Abreve;",[Char]
"\x0102")
  ,(BS
"abreve;",[Char]
"\x0103")
  ,(BS
"ac;",[Char]
"\x223E")
  ,(BS
"acd;",[Char]
"\x223F")
  ,(BS
"acE;",[Char]
"\x223E\x0333")
  ,(BS
"Acirc",[Char]
"\x00C2")
  ,(BS
"acirc",[Char]
"\x00E2")
  ,(BS
"Acirc;",[Char]
"\x00C2")
  ,(BS
"acirc;",[Char]
"\x00E2")
  ,(BS
"acute",[Char]
"\x00B4")
  ,(BS
"acute;",[Char]
"\x00B4")
  ,(BS
"Acy;",[Char]
"\x0410")
  ,(BS
"acy;",[Char]
"\x0430")
  ,(BS
"AElig",[Char]
"\x00C6")
  ,(BS
"aelig",[Char]
"\x00E6")
  ,(BS
"AElig;",[Char]
"\x00C6")
  ,(BS
"aelig;",[Char]
"\x00E6")
  ,(BS
"af;",[Char]
"\x2061")
  ,(BS
"Afr;",[Char]
"\xD835\xDD04")
  ,(BS
"afr;",[Char]
"\xD835\xDD1E")
  ,(BS
"Agrave",[Char]
"\x00C0")
  ,(BS
"agrave",[Char]
"\x00E0")
  ,(BS
"Agrave;",[Char]
"\x00C0")
  ,(BS
"agrave;",[Char]
"\x00E0")
  ,(BS
"alefsym;",[Char]
"\x2135")
  ,(BS
"aleph;",[Char]
"\x2135")
  ,(BS
"Alpha;",[Char]
"\x0391")
  ,(BS
"alpha;",[Char]
"\x03B1")
  ,(BS
"Amacr;",[Char]
"\x0100")
  ,(BS
"amacr;",[Char]
"\x0101")
  ,(BS
"amalg;",[Char]
"\x2A3F")
  ,(BS
"AMP",[Char]
"\x0026")
  ,(BS
"amp",[Char]
"\x0026")
  ,(BS
"AMP;",[Char]
"\x0026")
  ,(BS
"amp;",[Char]
"\x0026")
  ,(BS
"and;",[Char]
"\x2227")
  ,(BS
"And;",[Char]
"\x2A53")
  ,(BS
"andand;",[Char]
"\x2A55")
  ,(BS
"andd;",[Char]
"\x2A5C")
  ,(BS
"andslope;",[Char]
"\x2A58")
  ,(BS
"andv;",[Char]
"\x2A5A")
  ,(BS
"ang;",[Char]
"\x2220")
  ,(BS
"ange;",[Char]
"\x29A4")
  ,(BS
"angle;",[Char]
"\x2220")
  ,(BS
"angmsd;",[Char]
"\x2221")
  ,(BS
"angmsdaa;",[Char]
"\x29A8")
  ,(BS
"angmsdab;",[Char]
"\x29A9")
  ,(BS
"angmsdac;",[Char]
"\x29AA")
  ,(BS
"angmsdad;",[Char]
"\x29AB")
  ,(BS
"angmsdae;",[Char]
"\x29AC")
  ,(BS
"angmsdaf;",[Char]
"\x29AD")
  ,(BS
"angmsdag;",[Char]
"\x29AE")
  ,(BS
"angmsdah;",[Char]
"\x29AF")
  ,(BS
"angrt;",[Char]
"\x221F")
  ,(BS
"angrtvb;",[Char]
"\x22BE")
  ,(BS
"angrtvbd;",[Char]
"\x299D")
  ,(BS
"angsph;",[Char]
"\x2222")
  ,(BS
"angst;",[Char]
"\x00C5")
  ,(BS
"angzarr;",[Char]
"\x237C")
  ,(BS
"Aogon;",[Char]
"\x0104")
  ,(BS
"aogon;",[Char]
"\x0105")
  ,(BS
"Aopf;",[Char]
"\xD835\xDD38")
  ,(BS
"aopf;",[Char]
"\xD835\xDD52")
  ,(BS
"ap;",[Char]
"\x2248")
  ,(BS
"apacir;",[Char]
"\x2A6F")
  ,(BS
"ape;",[Char]
"\x224A")
  ,(BS
"apE;",[Char]
"\x2A70")
  ,(BS
"apid;",[Char]
"\x224B")
  ,(BS
"apos;",[Char]
"\x0027")
  ,(BS
"ApplyFunction;",[Char]
"\x2061")
  ,(BS
"approx;",[Char]
"\x2248")
  ,(BS
"approxeq;",[Char]
"\x224A")
  ,(BS
"Aring",[Char]
"\x00C5")
  ,(BS
"aring",[Char]
"\x00E5")
  ,(BS
"Aring;",[Char]
"\x00C5")
  ,(BS
"aring;",[Char]
"\x00E5")
  ,(BS
"Ascr;",[Char]
"\xD835\xDC9C")
  ,(BS
"ascr;",[Char]
"\xD835\xDCB6")
  ,(BS
"Assign;",[Char]
"\x2254")
  ,(BS
"ast;",[Char]
"\x002A")
  ,(BS
"asymp;",[Char]
"\x2248")
  ,(BS
"asympeq;",[Char]
"\x224D")
  ,(BS
"Atilde",[Char]
"\x00C3")
  ,(BS
"atilde",[Char]
"\x00E3")
  ,(BS
"Atilde;",[Char]
"\x00C3")
  ,(BS
"atilde;",[Char]
"\x00E3")
  ,(BS
"Auml",[Char]
"\x00C4")
  ,(BS
"auml",[Char]
"\x00E4")
  ,(BS
"Auml;",[Char]
"\x00C4")
  ,(BS
"auml;",[Char]
"\x00E4")
  ,(BS
"awconint;",[Char]
"\x2233")
  ,(BS
"awint;",[Char]
"\x2A11")
  ,(BS
"backcong;",[Char]
"\x224C")
  ,(BS
"backepsilon;",[Char]
"\x03F6")
  ,(BS
"backprime;",[Char]
"\x2035")
  ,(BS
"backsim;",[Char]
"\x223D")
  ,(BS
"backsimeq;",[Char]
"\x22CD")
  ,(BS
"Backslash;",[Char]
"\x2216")
  ,(BS
"Barv;",[Char]
"\x2AE7")
  ,(BS
"barvee;",[Char]
"\x22BD")
  ,(BS
"barwed;",[Char]
"\x2305")
  ,(BS
"Barwed;",[Char]
"\x2306")
  ,(BS
"barwedge;",[Char]
"\x2305")
  ,(BS
"bbrk;",[Char]
"\x23B5")
  ,(BS
"bbrktbrk;",[Char]
"\x23B6")
  ,(BS
"bcong;",[Char]
"\x224C")
  ,(BS
"Bcy;",[Char]
"\x0411")
  ,(BS
"bcy;",[Char]
"\x0431")
  ,(BS
"bdquo;",[Char]
"\x201E")
  ,(BS
"becaus;",[Char]
"\x2235")
  ,(BS
"Because;",[Char]
"\x2235")
  ,(BS
"because;",[Char]
"\x2235")
  ,(BS
"bemptyv;",[Char]
"\x29B0")
  ,(BS
"bepsi;",[Char]
"\x03F6")
  ,(BS
"bernou;",[Char]
"\x212C")
  ,(BS
"Bernoullis;",[Char]
"\x212C")
  ,(BS
"Beta;",[Char]
"\x0392")
  ,(BS
"beta;",[Char]
"\x03B2")
  ,(BS
"beth;",[Char]
"\x2136")
  ,(BS
"between;",[Char]
"\x226C")
  ,(BS
"Bfr;",[Char]
"\xD835\xDD05")
  ,(BS
"bfr;",[Char]
"\xD835\xDD1F")
  ,(BS
"bigcap;",[Char]
"\x22C2")
  ,(BS
"bigcirc;",[Char]
"\x25EF")
  ,(BS
"bigcup;",[Char]
"\x22C3")
  ,(BS
"bigodot;",[Char]
"\x2A00")
  ,(BS
"bigoplus;",[Char]
"\x2A01")
  ,(BS
"bigotimes;",[Char]
"\x2A02")
  ,(BS
"bigsqcup;",[Char]
"\x2A06")
  ,(BS
"bigstar;",[Char]
"\x2605")
  ,(BS
"bigtriangledown;",[Char]
"\x25BD")
  ,(BS
"bigtriangleup;",[Char]
"\x25B3")
  ,(BS
"biguplus;",[Char]
"\x2A04")
  ,(BS
"bigvee;",[Char]
"\x22C1")
  ,(BS
"bigwedge;",[Char]
"\x22C0")
  ,(BS
"bkarow;",[Char]
"\x290D")
  ,(BS
"blacklozenge;",[Char]
"\x29EB")
  ,(BS
"blacksquare;",[Char]
"\x25AA")
  ,(BS
"blacktriangle;",[Char]
"\x25B4")
  ,(BS
"blacktriangledown;",[Char]
"\x25BE")
  ,(BS
"blacktriangleleft;",[Char]
"\x25C2")
  ,(BS
"blacktriangleright;",[Char]
"\x25B8")
  ,(BS
"blank;",[Char]
"\x2423")
  ,(BS
"blk12;",[Char]
"\x2592")
  ,(BS
"blk14;",[Char]
"\x2591")
  ,(BS
"blk34;",[Char]
"\x2593")
  ,(BS
"block;",[Char]
"\x2588")
  ,(BS
"bne;",[Char]
"\x003D\x20E5")
  ,(BS
"bnequiv;",[Char]
"\x2261\x20E5")
  ,(BS
"bnot;",[Char]
"\x2310")
  ,(BS
"bNot;",[Char]
"\x2AED")
  ,(BS
"Bopf;",[Char]
"\xD835\xDD39")
  ,(BS
"bopf;",[Char]
"\xD835\xDD53")
  ,(BS
"bot;",[Char]
"\x22A5")
  ,(BS
"bottom;",[Char]
"\x22A5")
  ,(BS
"bowtie;",[Char]
"\x22C8")
  ,(BS
"boxbox;",[Char]
"\x29C9")
  ,(BS
"boxdl;",[Char]
"\x2510")
  ,(BS
"boxdL;",[Char]
"\x2555")
  ,(BS
"boxDl;",[Char]
"\x2556")
  ,(BS
"boxDL;",[Char]
"\x2557")
  ,(BS
"boxdr;",[Char]
"\x250C")
  ,(BS
"boxdR;",[Char]
"\x2552")
  ,(BS
"boxDr;",[Char]
"\x2553")
  ,(BS
"boxDR;",[Char]
"\x2554")
  ,(BS
"boxh;",[Char]
"\x2500")
  ,(BS
"boxH;",[Char]
"\x2550")
  ,(BS
"boxhd;",[Char]
"\x252C")
  ,(BS
"boxHd;",[Char]
"\x2564")
  ,(BS
"boxhD;",[Char]
"\x2565")
  ,(BS
"boxHD;",[Char]
"\x2566")
  ,(BS
"boxhu;",[Char]
"\x2534")
  ,(BS
"boxHu;",[Char]
"\x2567")
  ,(BS
"boxhU;",[Char]
"\x2568")
  ,(BS
"boxHU;",[Char]
"\x2569")
  ,(BS
"boxminus;",[Char]
"\x229F")
  ,(BS
"boxplus;",[Char]
"\x229E")
  ,(BS
"boxtimes;",[Char]
"\x22A0")
  ,(BS
"boxul;",[Char]
"\x2518")
  ,(BS
"boxuL;",[Char]
"\x255B")
  ,(BS
"boxUl;",[Char]
"\x255C")
  ,(BS
"boxUL;",[Char]
"\x255D")
  ,(BS
"boxur;",[Char]
"\x2514")
  ,(BS
"boxuR;",[Char]
"\x2558")
  ,(BS
"boxUr;",[Char]
"\x2559")
  ,(BS
"boxUR;",[Char]
"\x255A")
  ,(BS
"boxv;",[Char]
"\x2502")
  ,(BS
"boxV;",[Char]
"\x2551")
  ,(BS
"boxvh;",[Char]
"\x253C")
  ,(BS
"boxvH;",[Char]
"\x256A")
  ,(BS
"boxVh;",[Char]
"\x256B")
  ,(BS
"boxVH;",[Char]
"\x256C")
  ,(BS
"boxvl;",[Char]
"\x2524")
  ,(BS
"boxvL;",[Char]
"\x2561")
  ,(BS
"boxVl;",[Char]
"\x2562")
  ,(BS
"boxVL;",[Char]
"\x2563")
  ,(BS
"boxvr;",[Char]
"\x251C")
  ,(BS
"boxvR;",[Char]
"\x255E")
  ,(BS
"boxVr;",[Char]
"\x255F")
  ,(BS
"boxVR;",[Char]
"\x2560")
  ,(BS
"bprime;",[Char]
"\x2035")
  ,(BS
"Breve;",[Char]
"\x02D8")
  ,(BS
"breve;",[Char]
"\x02D8")
  ,(BS
"brvbar",[Char]
"\x00A6")
  ,(BS
"brvbar;",[Char]
"\x00A6")
  ,(BS
"Bscr;",[Char]
"\x212C")
  ,(BS
"bscr;",[Char]
"\xD835\xDCB7")
  ,(BS
"bsemi;",[Char]
"\x204F")
  ,(BS
"bsim;",[Char]
"\x223D")
  ,(BS
"bsime;",[Char]
"\x22CD")
  ,(BS
"bsol;",[Char]
"\x005C")
  ,(BS
"bsolb;",[Char]
"\x29C5")
  ,(BS
"bsolhsub;",[Char]
"\x27C8")
  ,(BS
"bull;",[Char]
"\x2022")
  ,(BS
"bullet;",[Char]
"\x2022")
  ,(BS
"bump;",[Char]
"\x224E")
  ,(BS
"bumpe;",[Char]
"\x224F")
  ,(BS
"bumpE;",[Char]
"\x2AAE")
  ,(BS
"Bumpeq;",[Char]
"\x224E")
  ,(BS
"bumpeq;",[Char]
"\x224F")
  ,(BS
"Cacute;",[Char]
"\x0106")
  ,(BS
"cacute;",[Char]
"\x0107")
  ,(BS
"cap;",[Char]
"\x2229")
  ,(BS
"Cap;",[Char]
"\x22D2")
  ,(BS
"capand;",[Char]
"\x2A44")
  ,(BS
"capbrcup;",[Char]
"\x2A49")
  ,(BS
"capcap;",[Char]
"\x2A4B")
  ,(BS
"capcup;",[Char]
"\x2A47")
  ,(BS
"capdot;",[Char]
"\x2A40")
  ,(BS
"CapitalDifferentialD;",[Char]
"\x2145")
  ,(BS
"caps;",[Char]
"\x2229\xFE00")
  ,(BS
"caret;",[Char]
"\x2041")
  ,(BS
"caron;",[Char]
"\x02C7")
  ,(BS
"Cayleys;",[Char]
"\x212D")
  ,(BS
"ccaps;",[Char]
"\x2A4D")
  ,(BS
"Ccaron;",[Char]
"\x010C")
  ,(BS
"ccaron;",[Char]
"\x010D")
  ,(BS
"Ccedil",[Char]
"\x00C7")
  ,(BS
"ccedil",[Char]
"\x00E7")
  ,(BS
"Ccedil;",[Char]
"\x00C7")
  ,(BS
"ccedil;",[Char]
"\x00E7")
  ,(BS
"Ccirc;",[Char]
"\x0108")
  ,(BS
"ccirc;",[Char]
"\x0109")
  ,(BS
"Cconint;",[Char]
"\x2230")
  ,(BS
"ccups;",[Char]
"\x2A4C")
  ,(BS
"ccupssm;",[Char]
"\x2A50")
  ,(BS
"Cdot;",[Char]
"\x010A")
  ,(BS
"cdot;",[Char]
"\x010B")
  ,(BS
"cedil",[Char]
"\x00B8")
  ,(BS
"cedil;",[Char]
"\x00B8")
  ,(BS
"Cedilla;",[Char]
"\x00B8")
  ,(BS
"cemptyv;",[Char]
"\x29B2")
  ,(BS
"cent",[Char]
"\x00A2")
  ,(BS
"cent;",[Char]
"\x00A2")
  ,(BS
"CenterDot;",[Char]
"\x00B7")
  ,(BS
"centerdot;",[Char]
"\x00B7")
  ,(BS
"Cfr;",[Char]
"\x212D")
  ,(BS
"cfr;",[Char]
"\xD835\xDD20")
  ,(BS
"CHcy;",[Char]
"\x0427")
  ,(BS
"chcy;",[Char]
"\x0447")
  ,(BS
"check;",[Char]
"\x2713")
  ,(BS
"checkmark;",[Char]
"\x2713")
  ,(BS
"Chi;",[Char]
"\x03A7")
  ,(BS
"chi;",[Char]
"\x03C7")
  ,(BS
"cir;",[Char]
"\x25CB")
  ,(BS
"circ;",[Char]
"\x02C6")
  ,(BS
"circeq;",[Char]
"\x2257")
  ,(BS
"circlearrowleft;",[Char]
"\x21BA")
  ,(BS
"circlearrowright;",[Char]
"\x21BB")
  ,(BS
"circledast;",[Char]
"\x229B")
  ,(BS
"circledcirc;",[Char]
"\x229A")
  ,(BS
"circleddash;",[Char]
"\x229D")
  ,(BS
"CircleDot;",[Char]
"\x2299")
  ,(BS
"circledR;",[Char]
"\x00AE")
  ,(BS
"circledS;",[Char]
"\x24C8")
  ,(BS
"CircleMinus;",[Char]
"\x2296")
  ,(BS
"CirclePlus;",[Char]
"\x2295")
  ,(BS
"CircleTimes;",[Char]
"\x2297")
  ,(BS
"cire;",[Char]
"\x2257")
  ,(BS
"cirE;",[Char]
"\x29C3")
  ,(BS
"cirfnint;",[Char]
"\x2A10")
  ,(BS
"cirmid;",[Char]
"\x2AEF")
  ,(BS
"cirscir;",[Char]
"\x29C2")
  ,(BS
"ClockwiseContourIntegral;",[Char]
"\x2232")
  ,(BS
"CloseCurlyDoubleQuote;",[Char]
"\x201D")
  ,(BS
"CloseCurlyQuote;",[Char]
"\x2019")
  ,(BS
"clubs;",[Char]
"\x2663")
  ,(BS
"clubsuit;",[Char]
"\x2663")
  ,(BS
"colon;",[Char]
"\x003A")
  ,(BS
"Colon;",[Char]
"\x2237")
  ,(BS
"colone;",[Char]
"\x2254")
  ,(BS
"Colone;",[Char]
"\x2A74")
  ,(BS
"coloneq;",[Char]
"\x2254")
  ,(BS
"comma;",[Char]
"\x002C")
  ,(BS
"commat;",[Char]
"\x0040")
  ,(BS
"comp;",[Char]
"\x2201")
  ,(BS
"compfn;",[Char]
"\x2218")
  ,(BS
"complement;",[Char]
"\x2201")
  ,(BS
"complexes;",[Char]
"\x2102")
  ,(BS
"cong;",[Char]
"\x2245")
  ,(BS
"congdot;",[Char]
"\x2A6D")
  ,(BS
"Congruent;",[Char]
"\x2261")
  ,(BS
"conint;",[Char]
"\x222E")
  ,(BS
"Conint;",[Char]
"\x222F")
  ,(BS
"ContourIntegral;",[Char]
"\x222E")
  ,(BS
"Copf;",[Char]
"\x2102")
  ,(BS
"copf;",[Char]
"\xD835\xDD54")
  ,(BS
"coprod;",[Char]
"\x2210")
  ,(BS
"Coproduct;",[Char]
"\x2210")
  ,(BS
"COPY",[Char]
"\x00A9")
  ,(BS
"copy",[Char]
"\x00A9")
  ,(BS
"COPY;",[Char]
"\x00A9")
  ,(BS
"copy;",[Char]
"\x00A9")
  ,(BS
"copysr;",[Char]
"\x2117")
  ,(BS
"CounterClockwiseContourIntegral;",[Char]
"\x2233")
  ,(BS
"crarr;",[Char]
"\x21B5")
  ,(BS
"cross;",[Char]
"\x2717")
  ,(BS
"Cross;",[Char]
"\x2A2F")
  ,(BS
"Cscr;",[Char]
"\xD835\xDC9E")
  ,(BS
"cscr;",[Char]
"\xD835\xDCB8")
  ,(BS
"csub;",[Char]
"\x2ACF")
  ,(BS
"csube;",[Char]
"\x2AD1")
  ,(BS
"csup;",[Char]
"\x2AD0")
  ,(BS
"csupe;",[Char]
"\x2AD2")
  ,(BS
"ctdot;",[Char]
"\x22EF")
  ,(BS
"cudarrl;",[Char]
"\x2938")
  ,(BS
"cudarrr;",[Char]
"\x2935")
  ,(BS
"cuepr;",[Char]
"\x22DE")
  ,(BS
"cuesc;",[Char]
"\x22DF")
  ,(BS
"cularr;",[Char]
"\x21B6")
  ,(BS
"cularrp;",[Char]
"\x293D")
  ,(BS
"cup;",[Char]
"\x222A")
  ,(BS
"Cup;",[Char]
"\x22D3")
  ,(BS
"cupbrcap;",[Char]
"\x2A48")
  ,(BS
"CupCap;",[Char]
"\x224D")
  ,(BS
"cupcap;",[Char]
"\x2A46")
  ,(BS
"cupcup;",[Char]
"\x2A4A")
  ,(BS
"cupdot;",[Char]
"\x228D")
  ,(BS
"cupor;",[Char]
"\x2A45")
  ,(BS
"cups;",[Char]
"\x222A\xFE00")
  ,(BS
"curarr;",[Char]
"\x21B7")
  ,(BS
"curarrm;",[Char]
"\x293C")
  ,(BS
"curlyeqprec;",[Char]
"\x22DE")
  ,(BS
"curlyeqsucc;",[Char]
"\x22DF")
  ,(BS
"curlyvee;",[Char]
"\x22CE")
  ,(BS
"curlywedge;",[Char]
"\x22CF")
  ,(BS
"curren",[Char]
"\x00A4")
  ,(BS
"curren;",[Char]
"\x00A4")
  ,(BS
"curvearrowleft;",[Char]
"\x21B6")
  ,(BS
"curvearrowright;",[Char]
"\x21B7")
  ,(BS
"cuvee;",[Char]
"\x22CE")
  ,(BS
"cuwed;",[Char]
"\x22CF")
  ,(BS
"cwconint;",[Char]
"\x2232")
  ,(BS
"cwint;",[Char]
"\x2231")
  ,(BS
"cylcty;",[Char]
"\x232D")
  ,(BS
"dagger;",[Char]
"\x2020")
  ,(BS
"Dagger;",[Char]
"\x2021")
  ,(BS
"daleth;",[Char]
"\x2138")
  ,(BS
"darr;",[Char]
"\x2193")
  ,(BS
"Darr;",[Char]
"\x21A1")
  ,(BS
"dArr;",[Char]
"\x21D3")
  ,(BS
"dash;",[Char]
"\x2010")
  ,(BS
"dashv;",[Char]
"\x22A3")
  ,(BS
"Dashv;",[Char]
"\x2AE4")
  ,(BS
"dbkarow;",[Char]
"\x290F")
  ,(BS
"dblac;",[Char]
"\x02DD")
  ,(BS
"Dcaron;",[Char]
"\x010E")
  ,(BS
"dcaron;",[Char]
"\x010F")
  ,(BS
"Dcy;",[Char]
"\x0414")
  ,(BS
"dcy;",[Char]
"\x0434")
  ,(BS
"DD;",[Char]
"\x2145")
  ,(BS
"dd;",[Char]
"\x2146")
  ,(BS
"ddagger;",[Char]
"\x2021")
  ,(BS
"ddarr;",[Char]
"\x21CA")
  ,(BS
"DDotrahd;",[Char]
"\x2911")
  ,(BS
"ddotseq;",[Char]
"\x2A77")
  ,(BS
"deg",[Char]
"\x00B0")
  ,(BS
"deg;",[Char]
"\x00B0")
  ,(BS
"Del;",[Char]
"\x2207")
  ,(BS
"Delta;",[Char]
"\x0394")
  ,(BS
"delta;",[Char]
"\x03B4")
  ,(BS
"demptyv;",[Char]
"\x29B1")
  ,(BS
"dfisht;",[Char]
"\x297F")
  ,(BS
"Dfr;",[Char]
"\xD835\xDD07")
  ,(BS
"dfr;",[Char]
"\xD835\xDD21")
  ,(BS
"dHar;",[Char]
"\x2965")
  ,(BS
"dharl;",[Char]
"\x21C3")
  ,(BS
"dharr;",[Char]
"\x21C2")
  ,(BS
"DiacriticalAcute;",[Char]
"\x00B4")
  ,(BS
"DiacriticalDot;",[Char]
"\x02D9")
  ,(BS
"DiacriticalDoubleAcute;",[Char]
"\x02DD")
  ,(BS
"DiacriticalGrave;",[Char]
"\x0060")
  ,(BS
"DiacriticalTilde;",[Char]
"\x02DC")
  ,(BS
"diam;",[Char]
"\x22C4")
  ,(BS
"Diamond;",[Char]
"\x22C4")
  ,(BS
"diamond;",[Char]
"\x22C4")
  ,(BS
"diamondsuit;",[Char]
"\x2666")
  ,(BS
"diams;",[Char]
"\x2666")
  ,(BS
"die;",[Char]
"\x00A8")
  ,(BS
"DifferentialD;",[Char]
"\x2146")
  ,(BS
"digamma;",[Char]
"\x03DD")
  ,(BS
"disin;",[Char]
"\x22F2")
  ,(BS
"div;",[Char]
"\x00F7")
  ,(BS
"divide",[Char]
"\x00F7")
  ,(BS
"divide;",[Char]
"\x00F7")
  ,(BS
"divideontimes;",[Char]
"\x22C7")
  ,(BS
"divonx;",[Char]
"\x22C7")
  ,(BS
"DJcy;",[Char]
"\x0402")
  ,(BS
"djcy;",[Char]
"\x0452")
  ,(BS
"dlcorn;",[Char]
"\x231E")
  ,(BS
"dlcrop;",[Char]
"\x230D")
  ,(BS
"dollar;",[Char]
"\x0024")
  ,(BS
"Dopf;",[Char]
"\xD835\xDD3B")
  ,(BS
"dopf;",[Char]
"\xD835\xDD55")
  ,(BS
"Dot;",[Char]
"\x00A8")
  ,(BS
"dot;",[Char]
"\x02D9")
  ,(BS
"DotDot;",[Char]
"\x20DC")
  ,(BS
"doteq;",[Char]
"\x2250")
  ,(BS
"doteqdot;",[Char]
"\x2251")
  ,(BS
"DotEqual;",[Char]
"\x2250")
  ,(BS
"dotminus;",[Char]
"\x2238")
  ,(BS
"dotplus;",[Char]
"\x2214")
  ,(BS
"dotsquare;",[Char]
"\x22A1")
  ,(BS
"doublebarwedge;",[Char]
"\x2306")
  ,(BS
"DoubleContourIntegral;",[Char]
"\x222F")
  ,(BS
"DoubleDot;",[Char]
"\x00A8")
  ,(BS
"DoubleDownArrow;",[Char]
"\x21D3")
  ,(BS
"DoubleLeftArrow;",[Char]
"\x21D0")
  ,(BS
"DoubleLeftRightArrow;",[Char]
"\x21D4")
  ,(BS
"DoubleLeftTee;",[Char]
"\x2AE4")
  ,(BS
"DoubleLongLeftArrow;",[Char]
"\x27F8")
  ,(BS
"DoubleLongLeftRightArrow;",[Char]
"\x27FA")
  ,(BS
"DoubleLongRightArrow;",[Char]
"\x27F9")
  ,(BS
"DoubleRightArrow;",[Char]
"\x21D2")
  ,(BS
"DoubleRightTee;",[Char]
"\x22A8")
  ,(BS
"DoubleUpArrow;",[Char]
"\x21D1")
  ,(BS
"DoubleUpDownArrow;",[Char]
"\x21D5")
  ,(BS
"DoubleVerticalBar;",[Char]
"\x2225")
  ,(BS
"DownArrow;",[Char]
"\x2193")
  ,(BS
"downarrow;",[Char]
"\x2193")
  ,(BS
"Downarrow;",[Char]
"\x21D3")
  ,(BS
"DownArrowBar;",[Char]
"\x2913")
  ,(BS
"DownArrowUpArrow;",[Char]
"\x21F5")
  ,(BS
"DownBreve;",[Char]
"\x0311")
  ,(BS
"downdownarrows;",[Char]
"\x21CA")
  ,(BS
"downharpoonleft;",[Char]
"\x21C3")
  ,(BS
"downharpoonright;",[Char]
"\x21C2")
  ,(BS
"DownLeftRightVector;",[Char]
"\x2950")
  ,(BS
"DownLeftTeeVector;",[Char]
"\x295E")
  ,(BS
"DownLeftVector;",[Char]
"\x21BD")
  ,(BS
"DownLeftVectorBar;",[Char]
"\x2956")
  ,(BS
"DownRightTeeVector;",[Char]
"\x295F")
  ,(BS
"DownRightVector;",[Char]
"\x21C1")
  ,(BS
"DownRightVectorBar;",[Char]
"\x2957")
  ,(BS
"DownTee;",[Char]
"\x22A4")
  ,(BS
"DownTeeArrow;",[Char]
"\x21A7")
  ,(BS
"drbkarow;",[Char]
"\x2910")
  ,(BS
"drcorn;",[Char]
"\x231F")
  ,(BS
"drcrop;",[Char]
"\x230C")
  ,(BS
"Dscr;",[Char]
"\xD835\xDC9F")
  ,(BS
"dscr;",[Char]
"\xD835\xDCB9")
  ,(BS
"DScy;",[Char]
"\x0405")
  ,(BS
"dscy;",[Char]
"\x0455")
  ,(BS
"dsol;",[Char]
"\x29F6")
  ,(BS
"Dstrok;",[Char]
"\x0110")
  ,(BS
"dstrok;",[Char]
"\x0111")
  ,(BS
"dtdot;",[Char]
"\x22F1")
  ,(BS
"dtri;",[Char]
"\x25BF")
  ,(BS
"dtrif;",[Char]
"\x25BE")
  ,(BS
"duarr;",[Char]
"\x21F5")
  ,(BS
"duhar;",[Char]
"\x296F")
  ,(BS
"dwangle;",[Char]
"\x29A6")
  ,(BS
"DZcy;",[Char]
"\x040F")
  ,(BS
"dzcy;",[Char]
"\x045F")
  ,(BS
"dzigrarr;",[Char]
"\x27FF")
  ,(BS
"Eacute",[Char]
"\x00C9")
  ,(BS
"eacute",[Char]
"\x00E9")
  ,(BS
"Eacute;",[Char]
"\x00C9")
  ,(BS
"eacute;",[Char]
"\x00E9")
  ,(BS
"easter;",[Char]
"\x2A6E")
  ,(BS
"Ecaron;",[Char]
"\x011A")
  ,(BS
"ecaron;",[Char]
"\x011B")
  ,(BS
"ecir;",[Char]
"\x2256")
  ,(BS
"Ecirc",[Char]
"\x00CA")
  ,(BS
"ecirc",[Char]
"\x00EA")
  ,(BS
"Ecirc;",[Char]
"\x00CA")
  ,(BS
"ecirc;",[Char]
"\x00EA")
  ,(BS
"ecolon;",[Char]
"\x2255")
  ,(BS
"Ecy;",[Char]
"\x042D")
  ,(BS
"ecy;",[Char]
"\x044D")
  ,(BS
"eDDot;",[Char]
"\x2A77")
  ,(BS
"Edot;",[Char]
"\x0116")
  ,(BS
"edot;",[Char]
"\x0117")
  ,(BS
"eDot;",[Char]
"\x2251")
  ,(BS
"ee;",[Char]
"\x2147")
  ,(BS
"efDot;",[Char]
"\x2252")
  ,(BS
"Efr;",[Char]
"\xD835\xDD08")
  ,(BS
"efr;",[Char]
"\xD835\xDD22")
  ,(BS
"eg;",[Char]
"\x2A9A")
  ,(BS
"Egrave",[Char]
"\x00C8")
  ,(BS
"egrave",[Char]
"\x00E8")
  ,(BS
"Egrave;",[Char]
"\x00C8")
  ,(BS
"egrave;",[Char]
"\x00E8")
  ,(BS
"egs;",[Char]
"\x2A96")
  ,(BS
"egsdot;",[Char]
"\x2A98")
  ,(BS
"el;",[Char]
"\x2A99")
  ,(BS
"Element;",[Char]
"\x2208")
  ,(BS
"elinters;",[Char]
"\x23E7")
  ,(BS
"ell;",[Char]
"\x2113")
  ,(BS
"els;",[Char]
"\x2A95")
  ,(BS
"elsdot;",[Char]
"\x2A97")
  ,(BS
"Emacr;",[Char]
"\x0112")
  ,(BS
"emacr;",[Char]
"\x0113")
  ,(BS
"empty;",[Char]
"\x2205")
  ,(BS
"emptyset;",[Char]
"\x2205")
  ,(BS
"EmptySmallSquare;",[Char]
"\x25FB")
  ,(BS
"emptyv;",[Char]
"\x2205")
  ,(BS
"EmptyVerySmallSquare;",[Char]
"\x25AB")
  ,(BS
"emsp13;",[Char]
"\x2004")
  ,(BS
"emsp14;",[Char]
"\x2005")
  ,(BS
"emsp;",[Char]
"\x2003")
  ,(BS
"ENG;",[Char]
"\x014A")
  ,(BS
"eng;",[Char]
"\x014B")
  ,(BS
"ensp;",[Char]
"\x2002")
  ,(BS
"Eogon;",[Char]
"\x0118")
  ,(BS
"eogon;",[Char]
"\x0119")
  ,(BS
"Eopf;",[Char]
"\xD835\xDD3C")
  ,(BS
"eopf;",[Char]
"\xD835\xDD56")
  ,(BS
"epar;",[Char]
"\x22D5")
  ,(BS
"eparsl;",[Char]
"\x29E3")
  ,(BS
"eplus;",[Char]
"\x2A71")
  ,(BS
"epsi;",[Char]
"\x03B5")
  ,(BS
"Epsilon;",[Char]
"\x0395")
  ,(BS
"epsilon;",[Char]
"\x03B5")
  ,(BS
"epsiv;",[Char]
"\x03F5")
  ,(BS
"eqcirc;",[Char]
"\x2256")
  ,(BS
"eqcolon;",[Char]
"\x2255")
  ,(BS
"eqsim;",[Char]
"\x2242")
  ,(BS
"eqslantgtr;",[Char]
"\x2A96")
  ,(BS
"eqslantless;",[Char]
"\x2A95")
  ,(BS
"Equal;",[Char]
"\x2A75")
  ,(BS
"equals;",[Char]
"\x003D")
  ,(BS
"EqualTilde;",[Char]
"\x2242")
  ,(BS
"equest;",[Char]
"\x225F")
  ,(BS
"Equilibrium;",[Char]
"\x21CC")
  ,(BS
"equiv;",[Char]
"\x2261")
  ,(BS
"equivDD;",[Char]
"\x2A78")
  ,(BS
"eqvparsl;",[Char]
"\x29E5")
  ,(BS
"erarr;",[Char]
"\x2971")
  ,(BS
"erDot;",[Char]
"\x2253")
  ,(BS
"escr;",[Char]
"\x212F")
  ,(BS
"Escr;",[Char]
"\x2130")
  ,(BS
"esdot;",[Char]
"\x2250")
  ,(BS
"esim;",[Char]
"\x2242")
  ,(BS
"Esim;",[Char]
"\x2A73")
  ,(BS
"Eta;",[Char]
"\x0397")
  ,(BS
"eta;",[Char]
"\x03B7")
  ,(BS
"ETH",[Char]
"\x00D0")
  ,(BS
"eth",[Char]
"\x00F0")
  ,(BS
"ETH;",[Char]
"\x00D0")
  ,(BS
"eth;",[Char]
"\x00F0")
  ,(BS
"Euml",[Char]
"\x00CB")
  ,(BS
"euml",[Char]
"\x00EB")
  ,(BS
"Euml;",[Char]
"\x00CB")
  ,(BS
"euml;",[Char]
"\x00EB")
  ,(BS
"euro;",[Char]
"\x20AC")
  ,(BS
"excl;",[Char]
"\x0021")
  ,(BS
"exist;",[Char]
"\x2203")
  ,(BS
"Exists;",[Char]
"\x2203")
  ,(BS
"expectation;",[Char]
"\x2130")
  ,(BS
"ExponentialE;",[Char]
"\x2147")
  ,(BS
"exponentiale;",[Char]
"\x2147")
  ,(BS
"fallingdotseq;",[Char]
"\x2252")
  ,(BS
"Fcy;",[Char]
"\x0424")
  ,(BS
"fcy;",[Char]
"\x0444")
  ,(BS
"female;",[Char]
"\x2640")
  ,(BS
"ffilig;",[Char]
"\xFB03")
  ,(BS
"fflig;",[Char]
"\xFB00")
  ,(BS
"ffllig;",[Char]
"\xFB04")
  ,(BS
"Ffr;",[Char]
"\xD835\xDD09")
  ,(BS
"ffr;",[Char]
"\xD835\xDD23")
  ,(BS
"filig;",[Char]
"\xFB01")
  ,(BS
"FilledSmallSquare;",[Char]
"\x25FC")
  ,(BS
"FilledVerySmallSquare;",[Char]
"\x25AA")
  ,(BS
"fjlig;",[Char]
"\x0066\x006A")
  ,(BS
"flat;",[Char]
"\x266D")
  ,(BS
"fllig;",[Char]
"\xFB02")
  ,(BS
"fltns;",[Char]
"\x25B1")
  ,(BS
"fnof;",[Char]
"\x0192")
  ,(BS
"Fopf;",[Char]
"\xD835\xDD3D")
  ,(BS
"fopf;",[Char]
"\xD835\xDD57")
  ,(BS
"ForAll;",[Char]
"\x2200")
  ,(BS
"forall;",[Char]
"\x2200")
  ,(BS
"fork;",[Char]
"\x22D4")
  ,(BS
"forkv;",[Char]
"\x2AD9")
  ,(BS
"Fouriertrf;",[Char]
"\x2131")
  ,(BS
"fpartint;",[Char]
"\x2A0D")
  ,(BS
"frac12",[Char]
"\x00BD")
  ,(BS
"frac12;",[Char]
"\x00BD")
  ,(BS
"frac13;",[Char]
"\x2153")
  ,(BS
"frac14",[Char]
"\x00BC")
  ,(BS
"frac14;",[Char]
"\x00BC")
  ,(BS
"frac15;",[Char]
"\x2155")
  ,(BS
"frac16;",[Char]
"\x2159")
  ,(BS
"frac18;",[Char]
"\x215B")
  ,(BS
"frac23;",[Char]
"\x2154")
  ,(BS
"frac25;",[Char]
"\x2156")
  ,(BS
"frac34",[Char]
"\x00BE")
  ,(BS
"frac34;",[Char]
"\x00BE")
  ,(BS
"frac35;",[Char]
"\x2157")
  ,(BS
"frac38;",[Char]
"\x215C")
  ,(BS
"frac45;",[Char]
"\x2158")
  ,(BS
"frac56;",[Char]
"\x215A")
  ,(BS
"frac58;",[Char]
"\x215D")
  ,(BS
"frac78;",[Char]
"\x215E")
  ,(BS
"frasl;",[Char]
"\x2044")
  ,(BS
"frown;",[Char]
"\x2322")
  ,(BS
"Fscr;",[Char]
"\x2131")
  ,(BS
"fscr;",[Char]
"\xD835\xDCBB")
  ,(BS
"gacute;",[Char]
"\x01F5")
  ,(BS
"Gamma;",[Char]
"\x0393")
  ,(BS
"gamma;",[Char]
"\x03B3")
  ,(BS
"Gammad;",[Char]
"\x03DC")
  ,(BS
"gammad;",[Char]
"\x03DD")
  ,(BS
"gap;",[Char]
"\x2A86")
  ,(BS
"Gbreve;",[Char]
"\x011E")
  ,(BS
"gbreve;",[Char]
"\x011F")
  ,(BS
"Gcedil;",[Char]
"\x0122")
  ,(BS
"Gcirc;",[Char]
"\x011C")
  ,(BS
"gcirc;",[Char]
"\x011D")
  ,(BS
"Gcy;",[Char]
"\x0413")
  ,(BS
"gcy;",[Char]
"\x0433")
  ,(BS
"Gdot;",[Char]
"\x0120")
  ,(BS
"gdot;",[Char]
"\x0121")
  ,(BS
"ge;",[Char]
"\x2265")
  ,(BS
"gE;",[Char]
"\x2267")
  ,(BS
"gel;",[Char]
"\x22DB")
  ,(BS
"gEl;",[Char]
"\x2A8C")
  ,(BS
"geq;",[Char]
"\x2265")
  ,(BS
"geqq;",[Char]
"\x2267")
  ,(BS
"geqslant;",[Char]
"\x2A7E")
  ,(BS
"ges;",[Char]
"\x2A7E")
  ,(BS
"gescc;",[Char]
"\x2AA9")
  ,(BS
"gesdot;",[Char]
"\x2A80")
  ,(BS
"gesdoto;",[Char]
"\x2A82")
  ,(BS
"gesdotol;",[Char]
"\x2A84")
  ,(BS
"gesl;",[Char]
"\x22DB\xFE00")
  ,(BS
"gesles;",[Char]
"\x2A94")
  ,(BS
"Gfr;",[Char]
"\xD835\xDD0A")
  ,(BS
"gfr;",[Char]
"\xD835\xDD24")
  ,(BS
"gg;",[Char]
"\x226B")
  ,(BS
"Gg;",[Char]
"\x22D9")
  ,(BS
"ggg;",[Char]
"\x22D9")
  ,(BS
"gimel;",[Char]
"\x2137")
  ,(BS
"GJcy;",[Char]
"\x0403")
  ,(BS
"gjcy;",[Char]
"\x0453")
  ,(BS
"gl;",[Char]
"\x2277")
  ,(BS
"gla;",[Char]
"\x2AA5")
  ,(BS
"glE;",[Char]
"\x2A92")
  ,(BS
"glj;",[Char]
"\x2AA4")
  ,(BS
"gnap;",[Char]
"\x2A8A")
  ,(BS
"gnapprox;",[Char]
"\x2A8A")
  ,(BS
"gnE;",[Char]
"\x2269")
  ,(BS
"gne;",[Char]
"\x2A88")
  ,(BS
"gneq;",[Char]
"\x2A88")
  ,(BS
"gneqq;",[Char]
"\x2269")
  ,(BS
"gnsim;",[Char]
"\x22E7")
  ,(BS
"Gopf;",[Char]
"\xD835\xDD3E")
  ,(BS
"gopf;",[Char]
"\xD835\xDD58")
  ,(BS
"grave;",[Char]
"\x0060")
  ,(BS
"GreaterEqual;",[Char]
"\x2265")
  ,(BS
"GreaterEqualLess;",[Char]
"\x22DB")
  ,(BS
"GreaterFullEqual;",[Char]
"\x2267")
  ,(BS
"GreaterGreater;",[Char]
"\x2AA2")
  ,(BS
"GreaterLess;",[Char]
"\x2277")
  ,(BS
"GreaterSlantEqual;",[Char]
"\x2A7E")
  ,(BS
"GreaterTilde;",[Char]
"\x2273")
  ,(BS
"gscr;",[Char]
"\x210A")
  ,(BS
"Gscr;",[Char]
"\xD835\xDCA2")
  ,(BS
"gsim;",[Char]
"\x2273")
  ,(BS
"gsime;",[Char]
"\x2A8E")
  ,(BS
"gsiml;",[Char]
"\x2A90")
  ,(BS
"GT",[Char]
"\x003E")
  ,(BS
"gt",[Char]
"\x003E")
  ,(BS
"GT;",[Char]
"\x003E")
  ,(BS
"gt;",[Char]
"\x003E")
  ,(BS
"Gt;",[Char]
"\x226B")
  ,(BS
"gtcc;",[Char]
"\x2AA7")
  ,(BS
"gtcir;",[Char]
"\x2A7A")
  ,(BS
"gtdot;",[Char]
"\x22D7")
  ,(BS
"gtlPar;",[Char]
"\x2995")
  ,(BS
"gtquest;",[Char]
"\x2A7C")
  ,(BS
"gtrapprox;",[Char]
"\x2A86")
  ,(BS
"gtrarr;",[Char]
"\x2978")
  ,(BS
"gtrdot;",[Char]
"\x22D7")
  ,(BS
"gtreqless;",[Char]
"\x22DB")
  ,(BS
"gtreqqless;",[Char]
"\x2A8C")
  ,(BS
"gtrless;",[Char]
"\x2277")
  ,(BS
"gtrsim;",[Char]
"\x2273")
  ,(BS
"gvertneqq;",[Char]
"\x2269\xFE00")
  ,(BS
"gvnE;",[Char]
"\x2269\xFE00")
  ,(BS
"Hacek;",[Char]
"\x02C7")
  ,(BS
"hairsp;",[Char]
"\x200A")
  ,(BS
"half;",[Char]
"\x00BD")
  ,(BS
"hamilt;",[Char]
"\x210B")
  ,(BS
"HARDcy;",[Char]
"\x042A")
  ,(BS
"hardcy;",[Char]
"\x044A")
  ,(BS
"harr;",[Char]
"\x2194")
  ,(BS
"hArr;",[Char]
"\x21D4")
  ,(BS
"harrcir;",[Char]
"\x2948")
  ,(BS
"harrw;",[Char]
"\x21AD")
  ,(BS
"Hat;",[Char]
"\x005E")
  ,(BS
"hbar;",[Char]
"\x210F")
  ,(BS
"Hcirc;",[Char]
"\x0124")
  ,(BS
"hcirc;",[Char]
"\x0125")
  ,(BS
"hearts;",[Char]
"\x2665")
  ,(BS
"heartsuit;",[Char]
"\x2665")
  ,(BS
"hellip;",[Char]
"\x2026")
  ,(BS
"hercon;",[Char]
"\x22B9")
  ,(BS
"Hfr;",[Char]
"\x210C")
  ,(BS
"hfr;",[Char]
"\xD835\xDD25")
  ,(BS
"HilbertSpace;",[Char]
"\x210B")
  ,(BS
"hksearow;",[Char]
"\x2925")
  ,(BS
"hkswarow;",[Char]
"\x2926")
  ,(BS
"hoarr;",[Char]
"\x21FF")
  ,(BS
"homtht;",[Char]
"\x223B")
  ,(BS
"hookleftarrow;",[Char]
"\x21A9")
  ,(BS
"hookrightarrow;",[Char]
"\x21AA")
  ,(BS
"Hopf;",[Char]
"\x210D")
  ,(BS
"hopf;",[Char]
"\xD835\xDD59")
  ,(BS
"horbar;",[Char]
"\x2015")
  ,(BS
"HorizontalLine;",[Char]
"\x2500")
  ,(BS
"Hscr;",[Char]
"\x210B")
  ,(BS
"hscr;",[Char]
"\xD835\xDCBD")
  ,(BS
"hslash;",[Char]
"\x210F")
  ,(BS
"Hstrok;",[Char]
"\x0126")
  ,(BS
"hstrok;",[Char]
"\x0127")
  ,(BS
"HumpDownHump;",[Char]
"\x224E")
  ,(BS
"HumpEqual;",[Char]
"\x224F")
  ,(BS
"hybull;",[Char]
"\x2043")
  ,(BS
"hyphen;",[Char]
"\x2010")
  ,(BS
"Iacute",[Char]
"\x00CD")
  ,(BS
"iacute",[Char]
"\x00ED")
  ,(BS
"Iacute;",[Char]
"\x00CD")
  ,(BS
"iacute;",[Char]
"\x00ED")
  ,(BS
"ic;",[Char]
"\x2063")
  ,(BS
"Icirc",[Char]
"\x00CE")
  ,(BS
"icirc",[Char]
"\x00EE")
  ,(BS
"Icirc;",[Char]
"\x00CE")
  ,(BS
"icirc;",[Char]
"\x00EE")
  ,(BS
"Icy;",[Char]
"\x0418")
  ,(BS
"icy;",[Char]
"\x0438")
  ,(BS
"Idot;",[Char]
"\x0130")
  ,(BS
"IEcy;",[Char]
"\x0415")
  ,(BS
"iecy;",[Char]
"\x0435")
  ,(BS
"iexcl",[Char]
"\x00A1")
  ,(BS
"iexcl;",[Char]
"\x00A1")
  ,(BS
"iff;",[Char]
"\x21D4")
  ,(BS
"Ifr;",[Char]
"\x2111")
  ,(BS
"ifr;",[Char]
"\xD835\xDD26")
  ,(BS
"Igrave",[Char]
"\x00CC")
  ,(BS
"igrave",[Char]
"\x00EC")
  ,(BS
"Igrave;",[Char]
"\x00CC")
  ,(BS
"igrave;",[Char]
"\x00EC")
  ,(BS
"ii;",[Char]
"\x2148")
  ,(BS
"iiiint;",[Char]
"\x2A0C")
  ,(BS
"iiint;",[Char]
"\x222D")
  ,(BS
"iinfin;",[Char]
"\x29DC")
  ,(BS
"iiota;",[Char]
"\x2129")
  ,(BS
"IJlig;",[Char]
"\x0132")
  ,(BS
"ijlig;",[Char]
"\x0133")
  ,(BS
"Im;",[Char]
"\x2111")
  ,(BS
"Imacr;",[Char]
"\x012A")
  ,(BS
"imacr;",[Char]
"\x012B")
  ,(BS
"image;",[Char]
"\x2111")
  ,(BS
"ImaginaryI;",[Char]
"\x2148")
  ,(BS
"imagline;",[Char]
"\x2110")
  ,(BS
"imagpart;",[Char]
"\x2111")
  ,(BS
"imath;",[Char]
"\x0131")
  ,(BS
"imof;",[Char]
"\x22B7")
  ,(BS
"imped;",[Char]
"\x01B5")
  ,(BS
"Implies;",[Char]
"\x21D2")
  ,(BS
"in;",[Char]
"\x2208")
  ,(BS
"incare;",[Char]
"\x2105")
  ,(BS
"infin;",[Char]
"\x221E")
  ,(BS
"infintie;",[Char]
"\x29DD")
  ,(BS
"inodot;",[Char]
"\x0131")
  ,(BS
"int;",[Char]
"\x222B")
  ,(BS
"Int;",[Char]
"\x222C")
  ,(BS
"intcal;",[Char]
"\x22BA")
  ,(BS
"integers;",[Char]
"\x2124")
  ,(BS
"Integral;",[Char]
"\x222B")
  ,(BS
"intercal;",[Char]
"\x22BA")
  ,(BS
"Intersection;",[Char]
"\x22C2")
  ,(BS
"intlarhk;",[Char]
"\x2A17")
  ,(BS
"intprod;",[Char]
"\x2A3C")
  ,(BS
"InvisibleComma;",[Char]
"\x2063")
  ,(BS
"InvisibleTimes;",[Char]
"\x2062")
  ,(BS
"IOcy;",[Char]
"\x0401")
  ,(BS
"iocy;",[Char]
"\x0451")
  ,(BS
"Iogon;",[Char]
"\x012E")
  ,(BS
"iogon;",[Char]
"\x012F")
  ,(BS
"Iopf;",[Char]
"\xD835\xDD40")
  ,(BS
"iopf;",[Char]
"\xD835\xDD5A")
  ,(BS
"Iota;",[Char]
"\x0399")
  ,(BS
"iota;",[Char]
"\x03B9")
  ,(BS
"iprod;",[Char]
"\x2A3C")
  ,(BS
"iquest",[Char]
"\x00BF")
  ,(BS
"iquest;",[Char]
"\x00BF")
  ,(BS
"Iscr;",[Char]
"\x2110")
  ,(BS
"iscr;",[Char]
"\xD835\xDCBE")
  ,(BS
"isin;",[Char]
"\x2208")
  ,(BS
"isindot;",[Char]
"\x22F5")
  ,(BS
"isinE;",[Char]
"\x22F9")
  ,(BS
"isins;",[Char]
"\x22F4")
  ,(BS
"isinsv;",[Char]
"\x22F3")
  ,(BS
"isinv;",[Char]
"\x2208")
  ,(BS
"it;",[Char]
"\x2062")
  ,(BS
"Itilde;",[Char]
"\x0128")
  ,(BS
"itilde;",[Char]
"\x0129")
  ,(BS
"Iukcy;",[Char]
"\x0406")
  ,(BS
"iukcy;",[Char]
"\x0456")
  ,(BS
"Iuml",[Char]
"\x00CF")
  ,(BS
"iuml",[Char]
"\x00EF")
  ,(BS
"Iuml;",[Char]
"\x00CF")
  ,(BS
"iuml;",[Char]
"\x00EF")
  ,(BS
"Jcirc;",[Char]
"\x0134")
  ,(BS
"jcirc;",[Char]
"\x0135")
  ,(BS
"Jcy;",[Char]
"\x0419")
  ,(BS
"jcy;",[Char]
"\x0439")
  ,(BS
"Jfr;",[Char]
"\xD835\xDD0D")
  ,(BS
"jfr;",[Char]
"\xD835\xDD27")
  ,(BS
"jmath;",[Char]
"\x0237")
  ,(BS
"Jopf;",[Char]
"\xD835\xDD41")
  ,(BS
"jopf;",[Char]
"\xD835\xDD5B")
  ,(BS
"Jscr;",[Char]
"\xD835\xDCA5")
  ,(BS
"jscr;",[Char]
"\xD835\xDCBF")
  ,(BS
"Jsercy;",[Char]
"\x0408")
  ,(BS
"jsercy;",[Char]
"\x0458")
  ,(BS
"Jukcy;",[Char]
"\x0404")
  ,(BS
"jukcy;",[Char]
"\x0454")
  ,(BS
"Kappa;",[Char]
"\x039A")
  ,(BS
"kappa;",[Char]
"\x03BA")
  ,(BS
"kappav;",[Char]
"\x03F0")
  ,(BS
"Kcedil;",[Char]
"\x0136")
  ,(BS
"kcedil;",[Char]
"\x0137")
  ,(BS
"Kcy;",[Char]
"\x041A")
  ,(BS
"kcy;",[Char]
"\x043A")
  ,(BS
"Kfr;",[Char]
"\xD835\xDD0E")
  ,(BS
"kfr;",[Char]
"\xD835\xDD28")
  ,(BS
"kgreen;",[Char]
"\x0138")
  ,(BS
"KHcy;",[Char]
"\x0425")
  ,(BS
"khcy;",[Char]
"\x0445")
  ,(BS
"KJcy;",[Char]
"\x040C")
  ,(BS
"kjcy;",[Char]
"\x045C")
  ,(BS
"Kopf;",[Char]
"\xD835\xDD42")
  ,(BS
"kopf;",[Char]
"\xD835\xDD5C")
  ,(BS
"Kscr;",[Char]
"\xD835\xDCA6")
  ,(BS
"kscr;",[Char]
"\xD835\xDCC0")
  ,(BS
"lAarr;",[Char]
"\x21DA")
  ,(BS
"Lacute;",[Char]
"\x0139")
  ,(BS
"lacute;",[Char]
"\x013A")
  ,(BS
"laemptyv;",[Char]
"\x29B4")
  ,(BS
"lagran;",[Char]
"\x2112")
  ,(BS
"Lambda;",[Char]
"\x039B")
  ,(BS
"lambda;",[Char]
"\x03BB")
  ,(BS
"lang;",[Char]
"\x27E8")
  ,(BS
"Lang;",[Char]
"\x27EA")
  ,(BS
"langd;",[Char]
"\x2991")
  ,(BS
"langle;",[Char]
"\x27E8")
  ,(BS
"lap;",[Char]
"\x2A85")
  ,(BS
"Laplacetrf;",[Char]
"\x2112")
  ,(BS
"laquo",[Char]
"\x00AB")
  ,(BS
"laquo;",[Char]
"\x00AB")
  ,(BS
"larr;",[Char]
"\x2190")
  ,(BS
"Larr;",[Char]
"\x219E")
  ,(BS
"lArr;",[Char]
"\x21D0")
  ,(BS
"larrb;",[Char]
"\x21E4")
  ,(BS
"larrbfs;",[Char]
"\x291F")
  ,(BS
"larrfs;",[Char]
"\x291D")
  ,(BS
"larrhk;",[Char]
"\x21A9")
  ,(BS
"larrlp;",[Char]
"\x21AB")
  ,(BS
"larrpl;",[Char]
"\x2939")
  ,(BS
"larrsim;",[Char]
"\x2973")
  ,(BS
"larrtl;",[Char]
"\x21A2")
  ,(BS
"lat;",[Char]
"\x2AAB")
  ,(BS
"latail;",[Char]
"\x2919")
  ,(BS
"lAtail;",[Char]
"\x291B")
  ,(BS
"late;",[Char]
"\x2AAD")
  ,(BS
"lates;",[Char]
"\x2AAD\xFE00")
  ,(BS
"lbarr;",[Char]
"\x290C")
  ,(BS
"lBarr;",[Char]
"\x290E")
  ,(BS
"lbbrk;",[Char]
"\x2772")
  ,(BS
"lbrace;",[Char]
"\x007B")
  ,(BS
"lbrack;",[Char]
"\x005B")
  ,(BS
"lbrke;",[Char]
"\x298B")
  ,(BS
"lbrksld;",[Char]
"\x298F")
  ,(BS
"lbrkslu;",[Char]
"\x298D")
  ,(BS
"Lcaron;",[Char]
"\x013D")
  ,(BS
"lcaron;",[Char]
"\x013E")
  ,(BS
"Lcedil;",[Char]
"\x013B")
  ,(BS
"lcedil;",[Char]
"\x013C")
  ,(BS
"lceil;",[Char]
"\x2308")
  ,(BS
"lcub;",[Char]
"\x007B")
  ,(BS
"Lcy;",[Char]
"\x041B")
  ,(BS
"lcy;",[Char]
"\x043B")
  ,(BS
"ldca;",[Char]
"\x2936")
  ,(BS
"ldquo;",[Char]
"\x201C")
  ,(BS
"ldquor;",[Char]
"\x201E")
  ,(BS
"ldrdhar;",[Char]
"\x2967")
  ,(BS
"ldrushar;",[Char]
"\x294B")
  ,(BS
"ldsh;",[Char]
"\x21B2")
  ,(BS
"le;",[Char]
"\x2264")
  ,(BS
"lE;",[Char]
"\x2266")
  ,(BS
"LeftAngleBracket;",[Char]
"\x27E8")
  ,(BS
"LeftArrow;",[Char]
"\x2190")
  ,(BS
"leftarrow;",[Char]
"\x2190")
  ,(BS
"Leftarrow;",[Char]
"\x21D0")
  ,(BS
"LeftArrowBar;",[Char]
"\x21E4")
  ,(BS
"LeftArrowRightArrow;",[Char]
"\x21C6")
  ,(BS
"leftarrowtail;",[Char]
"\x21A2")
  ,(BS
"LeftCeiling;",[Char]
"\x2308")
  ,(BS
"LeftDoubleBracket;",[Char]
"\x27E6")
  ,(BS
"LeftDownTeeVector;",[Char]
"\x2961")
  ,(BS
"LeftDownVector;",[Char]
"\x21C3")
  ,(BS
"LeftDownVectorBar;",[Char]
"\x2959")
  ,(BS
"LeftFloor;",[Char]
"\x230A")
  ,(BS
"leftharpoondown;",[Char]
"\x21BD")
  ,(BS
"leftharpoonup;",[Char]
"\x21BC")
  ,(BS
"leftleftarrows;",[Char]
"\x21C7")
  ,(BS
"LeftRightArrow;",[Char]
"\x2194")
  ,(BS
"leftrightarrow;",[Char]
"\x2194")
  ,(BS
"Leftrightarrow;",[Char]
"\x21D4")
  ,(BS
"leftrightarrows;",[Char]
"\x21C6")
  ,(BS
"leftrightharpoons;",[Char]
"\x21CB")
  ,(BS
"leftrightsquigarrow;",[Char]
"\x21AD")
  ,(BS
"LeftRightVector;",[Char]
"\x294E")
  ,(BS
"LeftTee;",[Char]
"\x22A3")
  ,(BS
"LeftTeeArrow;",[Char]
"\x21A4")
  ,(BS
"LeftTeeVector;",[Char]
"\x295A")
  ,(BS
"leftthreetimes;",[Char]
"\x22CB")
  ,(BS
"LeftTriangle;",[Char]
"\x22B2")
  ,(BS
"LeftTriangleBar;",[Char]
"\x29CF")
  ,(BS
"LeftTriangleEqual;",[Char]
"\x22B4")
  ,(BS
"LeftUpDownVector;",[Char]
"\x2951")
  ,(BS
"LeftUpTeeVector;",[Char]
"\x2960")
  ,(BS
"LeftUpVector;",[Char]
"\x21BF")
  ,(BS
"LeftUpVectorBar;",[Char]
"\x2958")
  ,(BS
"LeftVector;",[Char]
"\x21BC")
  ,(BS
"LeftVectorBar;",[Char]
"\x2952")
  ,(BS
"leg;",[Char]
"\x22DA")
  ,(BS
"lEg;",[Char]
"\x2A8B")
  ,(BS
"leq;",[Char]
"\x2264")
  ,(BS
"leqq;",[Char]
"\x2266")
  ,(BS
"leqslant;",[Char]
"\x2A7D")
  ,(BS
"les;",[Char]
"\x2A7D")
  ,(BS
"lescc;",[Char]
"\x2AA8")
  ,(BS
"lesdot;",[Char]
"\x2A7F")
  ,(BS
"lesdoto;",[Char]
"\x2A81")
  ,(BS
"lesdotor;",[Char]
"\x2A83")
  ,(BS
"lesg;",[Char]
"\x22DA\xFE00")
  ,(BS
"lesges;",[Char]
"\x2A93")
  ,(BS
"lessapprox;",[Char]
"\x2A85")
  ,(BS
"lessdot;",[Char]
"\x22D6")
  ,(BS
"lesseqgtr;",[Char]
"\x22DA")
  ,(BS
"lesseqqgtr;",[Char]
"\x2A8B")
  ,(BS
"LessEqualGreater;",[Char]
"\x22DA")
  ,(BS
"LessFullEqual;",[Char]
"\x2266")
  ,(BS
"LessGreater;",[Char]
"\x2276")
  ,(BS
"lessgtr;",[Char]
"\x2276")
  ,(BS
"LessLess;",[Char]
"\x2AA1")
  ,(BS
"lesssim;",[Char]
"\x2272")
  ,(BS
"LessSlantEqual;",[Char]
"\x2A7D")
  ,(BS
"LessTilde;",[Char]
"\x2272")
  ,(BS
"lfisht;",[Char]
"\x297C")
  ,(BS
"lfloor;",[Char]
"\x230A")
  ,(BS
"Lfr;",[Char]
"\xD835\xDD0F")
  ,(BS
"lfr;",[Char]
"\xD835\xDD29")
  ,(BS
"lg;",[Char]
"\x2276")
  ,(BS
"lgE;",[Char]
"\x2A91")
  ,(BS
"lHar;",[Char]
"\x2962")
  ,(BS
"lhard;",[Char]
"\x21BD")
  ,(BS
"lharu;",[Char]
"\x21BC")
  ,(BS
"lharul;",[Char]
"\x296A")
  ,(BS
"lhblk;",[Char]
"\x2584")
  ,(BS
"LJcy;",[Char]
"\x0409")
  ,(BS
"ljcy;",[Char]
"\x0459")
  ,(BS
"ll;",[Char]
"\x226A")
  ,(BS
"Ll;",[Char]
"\x22D8")
  ,(BS
"llarr;",[Char]
"\x21C7")
  ,(BS
"llcorner;",[Char]
"\x231E")
  ,(BS
"Lleftarrow;",[Char]
"\x21DA")
  ,(BS
"llhard;",[Char]
"\x296B")
  ,(BS
"lltri;",[Char]
"\x25FA")
  ,(BS
"Lmidot;",[Char]
"\x013F")
  ,(BS
"lmidot;",[Char]
"\x0140")
  ,(BS
"lmoust;",[Char]
"\x23B0")
  ,(BS
"lmoustache;",[Char]
"\x23B0")
  ,(BS
"lnap;",[Char]
"\x2A89")
  ,(BS
"lnapprox;",[Char]
"\x2A89")
  ,(BS
"lnE;",[Char]
"\x2268")
  ,(BS
"lne;",[Char]
"\x2A87")
  ,(BS
"lneq;",[Char]
"\x2A87")
  ,(BS
"lneqq;",[Char]
"\x2268")
  ,(BS
"lnsim;",[Char]
"\x22E6")
  ,(BS
"loang;",[Char]
"\x27EC")
  ,(BS
"loarr;",[Char]
"\x21FD")
  ,(BS
"lobrk;",[Char]
"\x27E6")
  ,(BS
"LongLeftArrow;",[Char]
"\x27F5")
  ,(BS
"longleftarrow;",[Char]
"\x27F5")
  ,(BS
"Longleftarrow;",[Char]
"\x27F8")
  ,(BS
"LongLeftRightArrow;",[Char]
"\x27F7")
  ,(BS
"longleftrightarrow;",[Char]
"\x27F7")
  ,(BS
"Longleftrightarrow;",[Char]
"\x27FA")
  ,(BS
"longmapsto;",[Char]
"\x27FC")
  ,(BS
"LongRightArrow;",[Char]
"\x27F6")
  ,(BS
"longrightarrow;",[Char]
"\x27F6")
  ,(BS
"Longrightarrow;",[Char]
"\x27F9")
  ,(BS
"looparrowleft;",[Char]
"\x21AB")
  ,(BS
"looparrowright;",[Char]
"\x21AC")
  ,(BS
"lopar;",[Char]
"\x2985")
  ,(BS
"Lopf;",[Char]
"\xD835\xDD43")
  ,(BS
"lopf;",[Char]
"\xD835\xDD5D")
  ,(BS
"loplus;",[Char]
"\x2A2D")
  ,(BS
"lotimes;",[Char]
"\x2A34")
  ,(BS
"lowast;",[Char]
"\x2217")
  ,(BS
"lowbar;",[Char]
"\x005F")
  ,(BS
"LowerLeftArrow;",[Char]
"\x2199")
  ,(BS
"LowerRightArrow;",[Char]
"\x2198")
  ,(BS
"loz;",[Char]
"\x25CA")
  ,(BS
"lozenge;",[Char]
"\x25CA")
  ,(BS
"lozf;",[Char]
"\x29EB")
  ,(BS
"lpar;",[Char]
"\x0028")
  ,(BS
"lparlt;",[Char]
"\x2993")
  ,(BS
"lrarr;",[Char]
"\x21C6")
  ,(BS
"lrcorner;",[Char]
"\x231F")
  ,(BS
"lrhar;",[Char]
"\x21CB")
  ,(BS
"lrhard;",[Char]
"\x296D")
  ,(BS
"lrm;",[Char]
"\x200E")
  ,(BS
"lrtri;",[Char]
"\x22BF")
  ,(BS
"lsaquo;",[Char]
"\x2039")
  ,(BS
"Lscr;",[Char]
"\x2112")
  ,(BS
"lscr;",[Char]
"\xD835\xDCC1")
  ,(BS
"Lsh;",[Char]
"\x21B0")
  ,(BS
"lsh;",[Char]
"\x21B0")
  ,(BS
"lsim;",[Char]
"\x2272")
  ,(BS
"lsime;",[Char]
"\x2A8D")
  ,(BS
"lsimg;",[Char]
"\x2A8F")
  ,(BS
"lsqb;",[Char]
"\x005B")
  ,(BS
"lsquo;",[Char]
"\x2018")
  ,(BS
"lsquor;",[Char]
"\x201A")
  ,(BS
"Lstrok;",[Char]
"\x0141")
  ,(BS
"lstrok;",[Char]
"\x0142")
  ,(BS
"LT",[Char]
"\x003C")
  ,(BS
"lt",[Char]
"\x003C")
  ,(BS
"LT;",[Char]
"\x003C")
  ,(BS
"lt;",[Char]
"\x003C")
  ,(BS
"Lt;",[Char]
"\x226A")
  ,(BS
"ltcc;",[Char]
"\x2AA6")
  ,(BS
"ltcir;",[Char]
"\x2A79")
  ,(BS
"ltdot;",[Char]
"\x22D6")
  ,(BS
"lthree;",[Char]
"\x22CB")
  ,(BS
"ltimes;",[Char]
"\x22C9")
  ,(BS
"ltlarr;",[Char]
"\x2976")
  ,(BS
"ltquest;",[Char]
"\x2A7B")
  ,(BS
"ltri;",[Char]
"\x25C3")
  ,(BS
"ltrie;",[Char]
"\x22B4")
  ,(BS
"ltrif;",[Char]
"\x25C2")
  ,(BS
"ltrPar;",[Char]
"\x2996")
  ,(BS
"lurdshar;",[Char]
"\x294A")
  ,(BS
"luruhar;",[Char]
"\x2966")
  ,(BS
"lvertneqq;",[Char]
"\x2268\xFE00")
  ,(BS
"lvnE;",[Char]
"\x2268\xFE00")
  ,(BS
"macr",[Char]
"\x00AF")
  ,(BS
"macr;",[Char]
"\x00AF")
  ,(BS
"male;",[Char]
"\x2642")
  ,(BS
"malt;",[Char]
"\x2720")
  ,(BS
"maltese;",[Char]
"\x2720")
  ,(BS
"map;",[Char]
"\x21A6")
  ,(BS
"Map;",[Char]
"\x2905")
  ,(BS
"mapsto;",[Char]
"\x21A6")
  ,(BS
"mapstodown;",[Char]
"\x21A7")
  ,(BS
"mapstoleft;",[Char]
"\x21A4")
  ,(BS
"mapstoup;",[Char]
"\x21A5")
  ,(BS
"marker;",[Char]
"\x25AE")
  ,(BS
"mcomma;",[Char]
"\x2A29")
  ,(BS
"Mcy;",[Char]
"\x041C")
  ,(BS
"mcy;",[Char]
"\x043C")
  ,(BS
"mdash;",[Char]
"\x2014")
  ,(BS
"mDDot;",[Char]
"\x223A")
  ,(BS
"measuredangle;",[Char]
"\x2221")
  ,(BS
"MediumSpace;",[Char]
"\x205F")
  ,(BS
"Mellintrf;",[Char]
"\x2133")
  ,(BS
"Mfr;",[Char]
"\xD835\xDD10")
  ,(BS
"mfr;",[Char]
"\xD835\xDD2A")
  ,(BS
"mho;",[Char]
"\x2127")
  ,(BS
"micro",[Char]
"\x00B5")
  ,(BS
"micro;",[Char]
"\x00B5")
  ,(BS
"mid;",[Char]
"\x2223")
  ,(BS
"midast;",[Char]
"\x002A")
  ,(BS
"midcir;",[Char]
"\x2AF0")
  ,(BS
"middot",[Char]
"\x00B7")
  ,(BS
"middot;",[Char]
"\x00B7")
  ,(BS
"minus;",[Char]
"\x2212")
  ,(BS
"minusb;",[Char]
"\x229F")
  ,(BS
"minusd;",[Char]
"\x2238")
  ,(BS
"minusdu;",[Char]
"\x2A2A")
  ,(BS
"MinusPlus;",[Char]
"\x2213")
  ,(BS
"mlcp;",[Char]
"\x2ADB")
  ,(BS
"mldr;",[Char]
"\x2026")
  ,(BS
"mnplus;",[Char]
"\x2213")
  ,(BS
"models;",[Char]
"\x22A7")
  ,(BS
"Mopf;",[Char]
"\xD835\xDD44")
  ,(BS
"mopf;",[Char]
"\xD835\xDD5E")
  ,(BS
"mp;",[Char]
"\x2213")
  ,(BS
"Mscr;",[Char]
"\x2133")
  ,(BS
"mscr;",[Char]
"\xD835\xDCC2")
  ,(BS
"mstpos;",[Char]
"\x223E")
  ,(BS
"Mu;",[Char]
"\x039C")
  ,(BS
"mu;",[Char]
"\x03BC")
  ,(BS
"multimap;",[Char]
"\x22B8")
  ,(BS
"mumap;",[Char]
"\x22B8")
  ,(BS
"nabla;",[Char]
"\x2207")
  ,(BS
"Nacute;",[Char]
"\x0143")
  ,(BS
"nacute;",[Char]
"\x0144")
  ,(BS
"nang;",[Char]
"\x2220\x20D2")
  ,(BS
"nap;",[Char]
"\x2249")
  ,(BS
"napE;",[Char]
"\x2A70\x0338")
  ,(BS
"napid;",[Char]
"\x224B\x0338")
  ,(BS
"napos;",[Char]
"\x0149")
  ,(BS
"napprox;",[Char]
"\x2249")
  ,(BS
"natur;",[Char]
"\x266E")
  ,(BS
"natural;",[Char]
"\x266E")
  ,(BS
"naturals;",[Char]
"\x2115")
  ,(BS
"nbsp",[Char]
"\x00A0")
  ,(BS
"nbsp;",[Char]
"\x00A0")
  ,(BS
"nbump;",[Char]
"\x224E\x0338")
  ,(BS
"nbumpe;",[Char]
"\x224F\x0338")
  ,(BS
"ncap;",[Char]
"\x2A43")
  ,(BS
"Ncaron;",[Char]
"\x0147")
  ,(BS
"ncaron;",[Char]
"\x0148")
  ,(BS
"Ncedil;",[Char]
"\x0145")
  ,(BS
"ncedil;",[Char]
"\x0146")
  ,(BS
"ncong;",[Char]
"\x2247")
  ,(BS
"ncongdot;",[Char]
"\x2A6D\x0338")
  ,(BS
"ncup;",[Char]
"\x2A42")
  ,(BS
"Ncy;",[Char]
"\x041D")
  ,(BS
"ncy;",[Char]
"\x043D")
  ,(BS
"ndash;",[Char]
"\x2013")
  ,(BS
"ne;",[Char]
"\x2260")
  ,(BS
"nearhk;",[Char]
"\x2924")
  ,(BS
"nearr;",[Char]
"\x2197")
  ,(BS
"neArr;",[Char]
"\x21D7")
  ,(BS
"nearrow;",[Char]
"\x2197")
  ,(BS
"nedot;",[Char]
"\x2250\x0338")
  ,(BS
"NegativeMediumSpace;",[Char]
"\x200B")
  ,(BS
"NegativeThickSpace;",[Char]
"\x200B")
  ,(BS
"NegativeThinSpace;",[Char]
"\x200B")
  ,(BS
"NegativeVeryThinSpace;",[Char]
"\x200B")
  ,(BS
"nequiv;",[Char]
"\x2262")
  ,(BS
"nesear;",[Char]
"\x2928")
  ,(BS
"nesim;",[Char]
"\x2242\x0338")
  ,(BS
"NestedGreaterGreater;",[Char]
"\x226B")
  ,(BS
"NestedLessLess;",[Char]
"\x226A")
  ,(BS
"NewLine;",[Char]
"\x000A")
  ,(BS
"nexist;",[Char]
"\x2204")
  ,(BS
"nexists;",[Char]
"\x2204")
  ,(BS
"Nfr;",[Char]
"\xD835\xDD11")
  ,(BS
"nfr;",[Char]
"\xD835\xDD2B")
  ,(BS
"ngE;",[Char]
"\x2267\x0338")
  ,(BS
"nge;",[Char]
"\x2271")
  ,(BS
"ngeq;",[Char]
"\x2271")
  ,(BS
"ngeqq;",[Char]
"\x2267\x0338")
  ,(BS
"ngeqslant;",[Char]
"\x2A7E\x0338")
  ,(BS
"nges;",[Char]
"\x2A7E\x0338")
  ,(BS
"nGg;",[Char]
"\x22D9\x0338")
  ,(BS
"ngsim;",[Char]
"\x2275")
  ,(BS
"nGt;",[Char]
"\x226B\x20D2")
  ,(BS
"ngt;",[Char]
"\x226F")
  ,(BS
"ngtr;",[Char]
"\x226F")
  ,(BS
"nGtv;",[Char]
"\x226B\x0338")
  ,(BS
"nharr;",[Char]
"\x21AE")
  ,(BS
"nhArr;",[Char]
"\x21CE")
  ,(BS
"nhpar;",[Char]
"\x2AF2")
  ,(BS
"ni;",[Char]
"\x220B")
  ,(BS
"nis;",[Char]
"\x22FC")
  ,(BS
"nisd;",[Char]
"\x22FA")
  ,(BS
"niv;",[Char]
"\x220B")
  ,(BS
"NJcy;",[Char]
"\x040A")
  ,(BS
"njcy;",[Char]
"\x045A")
  ,(BS
"nlarr;",[Char]
"\x219A")
  ,(BS
"nlArr;",[Char]
"\x21CD")
  ,(BS
"nldr;",[Char]
"\x2025")
  ,(BS
"nlE;",[Char]
"\x2266\x0338")
  ,(BS
"nle;",[Char]
"\x2270")
  ,(BS
"nleftarrow;",[Char]
"\x219A")
  ,(BS
"nLeftarrow;",[Char]
"\x21CD")
  ,(BS
"nleftrightarrow;",[Char]
"\x21AE")
  ,(BS
"nLeftrightarrow;",[Char]
"\x21CE")
  ,(BS
"nleq;",[Char]
"\x2270")
  ,(BS
"nleqq;",[Char]
"\x2266\x0338")
  ,(BS
"nleqslant;",[Char]
"\x2A7D\x0338")
  ,(BS
"nles;",[Char]
"\x2A7D\x0338")
  ,(BS
"nless;",[Char]
"\x226E")
  ,(BS
"nLl;",[Char]
"\x22D8\x0338")
  ,(BS
"nlsim;",[Char]
"\x2274")
  ,(BS
"nLt;",[Char]
"\x226A\x20D2")
  ,(BS
"nlt;",[Char]
"\x226E")
  ,(BS
"nltri;",[Char]
"\x22EA")
  ,(BS
"nltrie;",[Char]
"\x22EC")
  ,(BS
"nLtv;",[Char]
"\x226A\x0338")
  ,(BS
"nmid;",[Char]
"\x2224")
  ,(BS
"NoBreak;",[Char]
"\x2060")
  ,(BS
"NonBreakingSpace;",[Char]
"\x00A0")
  ,(BS
"Nopf;",[Char]
"\x2115")
  ,(BS
"nopf;",[Char]
"\xD835\xDD5F")
  ,(BS
"not",[Char]
"\x00AC")
  ,(BS
"not;",[Char]
"\x00AC")
  ,(BS
"Not;",[Char]
"\x2AEC")
  ,(BS
"NotCongruent;",[Char]
"\x2262")
  ,(BS
"NotCupCap;",[Char]
"\x226D")
  ,(BS
"NotDoubleVerticalBar;",[Char]
"\x2226")
  ,(BS
"NotElement;",[Char]
"\x2209")
  ,(BS
"NotEqual;",[Char]
"\x2260")
  ,(BS
"NotEqualTilde;",[Char]
"\x2242\x0338")
  ,(BS
"NotExists;",[Char]
"\x2204")
  ,(BS
"NotGreater;",[Char]
"\x226F")
  ,(BS
"NotGreaterEqual;",[Char]
"\x2271")
  ,(BS
"NotGreaterFullEqual;",[Char]
"\x2267\x0338")
  ,(BS
"NotGreaterGreater;",[Char]
"\x226B\x0338")
  ,(BS
"NotGreaterLess;",[Char]
"\x2279")
  ,(BS
"NotGreaterSlantEqual;",[Char]
"\x2A7E\x0338")
  ,(BS
"NotGreaterTilde;",[Char]
"\x2275")
  ,(BS
"NotHumpDownHump;",[Char]
"\x224E\x0338")
  ,(BS
"NotHumpEqual;",[Char]
"\x224F\x0338")
  ,(BS
"notin;",[Char]
"\x2209")
  ,(BS
"notindot;",[Char]
"\x22F5\x0338")
  ,(BS
"notinE;",[Char]
"\x22F9\x0338")
  ,(BS
"notinva;",[Char]
"\x2209")
  ,(BS
"notinvb;",[Char]
"\x22F7")
  ,(BS
"notinvc;",[Char]
"\x22F6")
  ,(BS
"NotLeftTriangle;",[Char]
"\x22EA")
  ,(BS
"NotLeftTriangleBar;",[Char]
"\x29CF\x0338")
  ,(BS
"NotLeftTriangleEqual;",[Char]
"\x22EC")
  ,(BS
"NotLess;",[Char]
"\x226E")
  ,(BS
"NotLessEqual;",[Char]
"\x2270")
  ,(BS
"NotLessGreater;",[Char]
"\x2278")
  ,(BS
"NotLessLess;",[Char]
"\x226A\x0338")
  ,(BS
"NotLessSlantEqual;",[Char]
"\x2A7D\x0338")
  ,(BS
"NotLessTilde;",[Char]
"\x2274")
  ,(BS
"NotNestedGreaterGreater;",[Char]
"\x2AA2\x0338")
  ,(BS
"NotNestedLessLess;",[Char]
"\x2AA1\x0338")
  ,(BS
"notni;",[Char]
"\x220C")
  ,(BS
"notniva;",[Char]
"\x220C")
  ,(BS
"notnivb;",[Char]
"\x22FE")
  ,(BS
"notnivc;",[Char]
"\x22FD")
  ,(BS
"NotPrecedes;",[Char]
"\x2280")
  ,(BS
"NotPrecedesEqual;",[Char]
"\x2AAF\x0338")
  ,(BS
"NotPrecedesSlantEqual;",[Char]
"\x22E0")
  ,(BS
"NotReverseElement;",[Char]
"\x220C")
  ,(BS
"NotRightTriangle;",[Char]
"\x22EB")
  ,(BS
"NotRightTriangleBar;",[Char]
"\x29D0\x0338")
  ,(BS
"NotRightTriangleEqual;",[Char]
"\x22ED")
  ,(BS
"NotSquareSubset;",[Char]
"\x228F\x0338")
  ,(BS
"NotSquareSubsetEqual;",[Char]
"\x22E2")
  ,(BS
"NotSquareSuperset;",[Char]
"\x2290\x0338")
  ,(BS
"NotSquareSupersetEqual;",[Char]
"\x22E3")
  ,(BS
"NotSubset;",[Char]
"\x2282\x20D2")
  ,(BS
"NotSubsetEqual;",[Char]
"\x2288")
  ,(BS
"NotSucceeds;",[Char]
"\x2281")
  ,(BS
"NotSucceedsEqual;",[Char]
"\x2AB0\x0338")
  ,(BS
"NotSucceedsSlantEqual;",[Char]
"\x22E1")
  ,(BS
"NotSucceedsTilde;",[Char]
"\x227F\x0338")
  ,(BS
"NotSuperset;",[Char]
"\x2283\x20D2")
  ,(BS
"NotSupersetEqual;",[Char]
"\x2289")
  ,(BS
"NotTilde;",[Char]
"\x2241")
  ,(BS
"NotTildeEqual;",[Char]
"\x2244")
  ,(BS
"NotTildeFullEqual;",[Char]
"\x2247")
  ,(BS
"NotTildeTilde;",[Char]
"\x2249")
  ,(BS
"NotVerticalBar;",[Char]
"\x2224")
  ,(BS
"npar;",[Char]
"\x2226")
  ,(BS
"nparallel;",[Char]
"\x2226")
  ,(BS
"nparsl;",[Char]
"\x2AFD\x20E5")
  ,(BS
"npart;",[Char]
"\x2202\x0338")
  ,(BS
"npolint;",[Char]
"\x2A14")
  ,(BS
"npr;",[Char]
"\x2280")
  ,(BS
"nprcue;",[Char]
"\x22E0")
  ,(BS
"npre;",[Char]
"\x2AAF\x0338")
  ,(BS
"nprec;",[Char]
"\x2280")
  ,(BS
"npreceq;",[Char]
"\x2AAF\x0338")
  ,(BS
"nrarr;",[Char]
"\x219B")
  ,(BS
"nrArr;",[Char]
"\x21CF")
  ,(BS
"nrarrc;",[Char]
"\x2933\x0338")
  ,(BS
"nrarrw;",[Char]
"\x219D\x0338")
  ,(BS
"nrightarrow;",[Char]
"\x219B")
  ,(BS
"nRightarrow;",[Char]
"\x21CF")
  ,(BS
"nrtri;",[Char]
"\x22EB")
  ,(BS
"nrtrie;",[Char]
"\x22ED")
  ,(BS
"nsc;",[Char]
"\x2281")
  ,(BS
"nsccue;",[Char]
"\x22E1")
  ,(BS
"nsce;",[Char]
"\x2AB0\x0338")
  ,(BS
"Nscr;",[Char]
"\xD835\xDCA9")
  ,(BS
"nscr;",[Char]
"\xD835\xDCC3")
  ,(BS
"nshortmid;",[Char]
"\x2224")
  ,(BS
"nshortparallel;",[Char]
"\x2226")
  ,(BS
"nsim;",[Char]
"\x2241")
  ,(BS
"nsime;",[Char]
"\x2244")
  ,(BS
"nsimeq;",[Char]
"\x2244")
  ,(BS
"nsmid;",[Char]
"\x2224")
  ,(BS
"nspar;",[Char]
"\x2226")
  ,(BS
"nsqsube;",[Char]
"\x22E2")
  ,(BS
"nsqsupe;",[Char]
"\x22E3")
  ,(BS
"nsub;",[Char]
"\x2284")
  ,(BS
"nsube;",[Char]
"\x2288")
  ,(BS
"nsubE;",[Char]
"\x2AC5\x0338")
  ,(BS
"nsubset;",[Char]
"\x2282\x20D2")
  ,(BS
"nsubseteq;",[Char]
"\x2288")
  ,(BS
"nsubseteqq;",[Char]
"\x2AC5\x0338")
  ,(BS
"nsucc;",[Char]
"\x2281")
  ,(BS
"nsucceq;",[Char]
"\x2AB0\x0338")
  ,(BS
"nsup;",[Char]
"\x2285")
  ,(BS
"nsupe;",[Char]
"\x2289")
  ,(BS
"nsupE;",[Char]
"\x2AC6\x0338")
  ,(BS
"nsupset;",[Char]
"\x2283\x20D2")
  ,(BS
"nsupseteq;",[Char]
"\x2289")
  ,(BS
"nsupseteqq;",[Char]
"\x2AC6\x0338")
  ,(BS
"ntgl;",[Char]
"\x2279")
  ,(BS
"Ntilde",[Char]
"\x00D1")
  ,(BS
"ntilde",[Char]
"\x00F1")
  ,(BS
"Ntilde;",[Char]
"\x00D1")
  ,(BS
"ntilde;",[Char]
"\x00F1")
  ,(BS
"ntlg;",[Char]
"\x2278")
  ,(BS
"ntriangleleft;",[Char]
"\x22EA")
  ,(BS
"ntrianglelefteq;",[Char]
"\x22EC")
  ,(BS
"ntriangleright;",[Char]
"\x22EB")
  ,(BS
"ntrianglerighteq;",[Char]
"\x22ED")
  ,(BS
"Nu;",[Char]
"\x039D")
  ,(BS
"nu;",[Char]
"\x03BD")
  ,(BS
"num;",[Char]
"\x0023")
  ,(BS
"numero;",[Char]
"\x2116")
  ,(BS
"numsp;",[Char]
"\x2007")
  ,(BS
"nvap;",[Char]
"\x224D\x20D2")
  ,(BS
"nvdash;",[Char]
"\x22AC")
  ,(BS
"nvDash;",[Char]
"\x22AD")
  ,(BS
"nVdash;",[Char]
"\x22AE")
  ,(BS
"nVDash;",[Char]
"\x22AF")
  ,(BS
"nvge;",[Char]
"\x2265\x20D2")
  ,(BS
"nvgt;",[Char]
"\x003E\x20D2")
  ,(BS
"nvHarr;",[Char]
"\x2904")
  ,(BS
"nvinfin;",[Char]
"\x29DE")
  ,(BS
"nvlArr;",[Char]
"\x2902")
  ,(BS
"nvle;",[Char]
"\x2264\x20D2")
  ,(BS
"nvlt;",[Char]
"\x003C\x20D2")
  ,(BS
"nvltrie;",[Char]
"\x22B4\x20D2")
  ,(BS
"nvrArr;",[Char]
"\x2903")
  ,(BS
"nvrtrie;",[Char]
"\x22B5\x20D2")
  ,(BS
"nvsim;",[Char]
"\x223C\x20D2")
  ,(BS
"nwarhk;",[Char]
"\x2923")
  ,(BS
"nwarr;",[Char]
"\x2196")
  ,(BS
"nwArr;",[Char]
"\x21D6")
  ,(BS
"nwarrow;",[Char]
"\x2196")
  ,(BS
"nwnear;",[Char]
"\x2927")
  ,(BS
"Oacute",[Char]
"\x00D3")
  ,(BS
"oacute",[Char]
"\x00F3")
  ,(BS
"Oacute;",[Char]
"\x00D3")
  ,(BS
"oacute;",[Char]
"\x00F3")
  ,(BS
"oast;",[Char]
"\x229B")
  ,(BS
"ocir;",[Char]
"\x229A")
  ,(BS
"Ocirc",[Char]
"\x00D4")
  ,(BS
"ocirc",[Char]
"\x00F4")
  ,(BS
"Ocirc;",[Char]
"\x00D4")
  ,(BS
"ocirc;",[Char]
"\x00F4")
  ,(BS
"Ocy;",[Char]
"\x041E")
  ,(BS
"ocy;",[Char]
"\x043E")
  ,(BS
"odash;",[Char]
"\x229D")
  ,(BS
"Odblac;",[Char]
"\x0150")
  ,(BS
"odblac;",[Char]
"\x0151")
  ,(BS
"odiv;",[Char]
"\x2A38")
  ,(BS
"odot;",[Char]
"\x2299")
  ,(BS
"odsold;",[Char]
"\x29BC")
  ,(BS
"OElig;",[Char]
"\x0152")
  ,(BS
"oelig;",[Char]
"\x0153")
  ,(BS
"ofcir;",[Char]
"\x29BF")
  ,(BS
"Ofr;",[Char]
"\xD835\xDD12")
  ,(BS
"ofr;",[Char]
"\xD835\xDD2C")
  ,(BS
"ogon;",[Char]
"\x02DB")
  ,(BS
"Ograve",[Char]
"\x00D2")
  ,(BS
"ograve",[Char]
"\x00F2")
  ,(BS
"Ograve;",[Char]
"\x00D2")
  ,(BS
"ograve;",[Char]
"\x00F2")
  ,(BS
"ogt;",[Char]
"\x29C1")
  ,(BS
"ohbar;",[Char]
"\x29B5")
  ,(BS
"ohm;",[Char]
"\x03A9")
  ,(BS
"oint;",[Char]
"\x222E")
  ,(BS
"olarr;",[Char]
"\x21BA")
  ,(BS
"olcir;",[Char]
"\x29BE")
  ,(BS
"olcross;",[Char]
"\x29BB")
  ,(BS
"oline;",[Char]
"\x203E")
  ,(BS
"olt;",[Char]
"\x29C0")
  ,(BS
"Omacr;",[Char]
"\x014C")
  ,(BS
"omacr;",[Char]
"\x014D")
  ,(BS
"Omega;",[Char]
"\x03A9")
  ,(BS
"omega;",[Char]
"\x03C9")
  ,(BS
"Omicron;",[Char]
"\x039F")
  ,(BS
"omicron;",[Char]
"\x03BF")
  ,(BS
"omid;",[Char]
"\x29B6")
  ,(BS
"ominus;",[Char]
"\x2296")
  ,(BS
"Oopf;",[Char]
"\xD835\xDD46")
  ,(BS
"oopf;",[Char]
"\xD835\xDD60")
  ,(BS
"opar;",[Char]
"\x29B7")
  ,(BS
"OpenCurlyDoubleQuote;",[Char]
"\x201C")
  ,(BS
"OpenCurlyQuote;",[Char]
"\x2018")
  ,(BS
"operp;",[Char]
"\x29B9")
  ,(BS
"oplus;",[Char]
"\x2295")
  ,(BS
"or;",[Char]
"\x2228")
  ,(BS
"Or;",[Char]
"\x2A54")
  ,(BS
"orarr;",[Char]
"\x21BB")
  ,(BS
"ord;",[Char]
"\x2A5D")
  ,(BS
"order;",[Char]
"\x2134")
  ,(BS
"orderof;",[Char]
"\x2134")
  ,(BS
"ordf",[Char]
"\x00AA")
  ,(BS
"ordf;",[Char]
"\x00AA")
  ,(BS
"ordm",[Char]
"\x00BA")
  ,(BS
"ordm;",[Char]
"\x00BA")
  ,(BS
"origof;",[Char]
"\x22B6")
  ,(BS
"oror;",[Char]
"\x2A56")
  ,(BS
"orslope;",[Char]
"\x2A57")
  ,(BS
"orv;",[Char]
"\x2A5B")
  ,(BS
"oS;",[Char]
"\x24C8")
  ,(BS
"oscr;",[Char]
"\x2134")
  ,(BS
"Oscr;",[Char]
"\xD835\xDCAA")
  ,(BS
"Oslash",[Char]
"\x00D8")
  ,(BS
"oslash",[Char]
"\x00F8")
  ,(BS
"Oslash;",[Char]
"\x00D8")
  ,(BS
"oslash;",[Char]
"\x00F8")
  ,(BS
"osol;",[Char]
"\x2298")
  ,(BS
"Otilde",[Char]
"\x00D5")
  ,(BS
"otilde",[Char]
"\x00F5")
  ,(BS
"Otilde;",[Char]
"\x00D5")
  ,(BS
"otilde;",[Char]
"\x00F5")
  ,(BS
"otimes;",[Char]
"\x2297")
  ,(BS
"Otimes;",[Char]
"\x2A37")
  ,(BS
"otimesas;",[Char]
"\x2A36")
  ,(BS
"Ouml",[Char]
"\x00D6")
  ,(BS
"ouml",[Char]
"\x00F6")
  ,(BS
"Ouml;",[Char]
"\x00D6")
  ,(BS
"ouml;",[Char]
"\x00F6")
  ,(BS
"ovbar;",[Char]
"\x233D")
  ,(BS
"OverBar;",[Char]
"\x203E")
  ,(BS
"OverBrace;",[Char]
"\x23DE")
  ,(BS
"OverBracket;",[Char]
"\x23B4")
  ,(BS
"OverParenthesis;",[Char]
"\x23DC")
  ,(BS
"par;",[Char]
"\x2225")
  ,(BS
"para",[Char]
"\x00B6")
  ,(BS
"para;",[Char]
"\x00B6")
  ,(BS
"parallel;",[Char]
"\x2225")
  ,(BS
"parsim;",[Char]
"\x2AF3")
  ,(BS
"parsl;",[Char]
"\x2AFD")
  ,(BS
"part;",[Char]
"\x2202")
  ,(BS
"PartialD;",[Char]
"\x2202")
  ,(BS
"Pcy;",[Char]
"\x041F")
  ,(BS
"pcy;",[Char]
"\x043F")
  ,(BS
"percnt;",[Char]
"\x0025")
  ,(BS
"period;",[Char]
"\x002E")
  ,(BS
"permil;",[Char]
"\x2030")
  ,(BS
"perp;",[Char]
"\x22A5")
  ,(BS
"pertenk;",[Char]
"\x2031")
  ,(BS
"Pfr;",[Char]
"\xD835\xDD13")
  ,(BS
"pfr;",[Char]
"\xD835\xDD2D")
  ,(BS
"Phi;",[Char]
"\x03A6")
  ,(BS
"phi;",[Char]
"\x03C6")
  ,(BS
"phiv;",[Char]
"\x03D5")
  ,(BS
"phmmat;",[Char]
"\x2133")
  ,(BS
"phone;",[Char]
"\x260E")
  ,(BS
"Pi;",[Char]
"\x03A0")
  ,(BS
"pi;",[Char]
"\x03C0")
  ,(BS
"pitchfork;",[Char]
"\x22D4")
  ,(BS
"piv;",[Char]
"\x03D6")
  ,(BS
"planck;",[Char]
"\x210F")
  ,(BS
"planckh;",[Char]
"\x210E")
  ,(BS
"plankv;",[Char]
"\x210F")
  ,(BS
"plus;",[Char]
"\x002B")
  ,(BS
"plusacir;",[Char]
"\x2A23")
  ,(BS
"plusb;",[Char]
"\x229E")
  ,(BS
"pluscir;",[Char]
"\x2A22")
  ,(BS
"plusdo;",[Char]
"\x2214")
  ,(BS
"plusdu;",[Char]
"\x2A25")
  ,(BS
"pluse;",[Char]
"\x2A72")
  ,(BS
"PlusMinus;",[Char]
"\x00B1")
  ,(BS
"plusmn",[Char]
"\x00B1")
  ,(BS
"plusmn;",[Char]
"\x00B1")
  ,(BS
"plussim;",[Char]
"\x2A26")
  ,(BS
"plustwo;",[Char]
"\x2A27")
  ,(BS
"pm;",[Char]
"\x00B1")
  ,(BS
"Poincareplane;",[Char]
"\x210C")
  ,(BS
"pointint;",[Char]
"\x2A15")
  ,(BS
"Popf;",[Char]
"\x2119")
  ,(BS
"popf;",[Char]
"\xD835\xDD61")
  ,(BS
"pound",[Char]
"\x00A3")
  ,(BS
"pound;",[Char]
"\x00A3")
  ,(BS
"pr;",[Char]
"\x227A")
  ,(BS
"Pr;",[Char]
"\x2ABB")
  ,(BS
"prap;",[Char]
"\x2AB7")
  ,(BS
"prcue;",[Char]
"\x227C")
  ,(BS
"pre;",[Char]
"\x2AAF")
  ,(BS
"prE;",[Char]
"\x2AB3")
  ,(BS
"prec;",[Char]
"\x227A")
  ,(BS
"precapprox;",[Char]
"\x2AB7")
  ,(BS
"preccurlyeq;",[Char]
"\x227C")
  ,(BS
"Precedes;",[Char]
"\x227A")
  ,(BS
"PrecedesEqual;",[Char]
"\x2AAF")
  ,(BS
"PrecedesSlantEqual;",[Char]
"\x227C")
  ,(BS
"PrecedesTilde;",[Char]
"\x227E")
  ,(BS
"preceq;",[Char]
"\x2AAF")
  ,(BS
"precnapprox;",[Char]
"\x2AB9")
  ,(BS
"precneqq;",[Char]
"\x2AB5")
  ,(BS
"precnsim;",[Char]
"\x22E8")
  ,(BS
"precsim;",[Char]
"\x227E")
  ,(BS
"prime;",[Char]
"\x2032")
  ,(BS
"Prime;",[Char]
"\x2033")
  ,(BS
"primes;",[Char]
"\x2119")
  ,(BS
"prnap;",[Char]
"\x2AB9")
  ,(BS
"prnE;",[Char]
"\x2AB5")
  ,(BS
"prnsim;",[Char]
"\x22E8")
  ,(BS
"prod;",[Char]
"\x220F")
  ,(BS
"Product;",[Char]
"\x220F")
  ,(BS
"profalar;",[Char]
"\x232E")
  ,(BS
"profline;",[Char]
"\x2312")
  ,(BS
"profsurf;",[Char]
"\x2313")
  ,(BS
"prop;",[Char]
"\x221D")
  ,(BS
"Proportion;",[Char]
"\x2237")
  ,(BS
"Proportional;",[Char]
"\x221D")
  ,(BS
"propto;",[Char]
"\x221D")
  ,(BS
"prsim;",[Char]
"\x227E")
  ,(BS
"prurel;",[Char]
"\x22B0")
  ,(BS
"Pscr;",[Char]
"\xD835\xDCAB")
  ,(BS
"pscr;",[Char]
"\xD835\xDCC5")
  ,(BS
"Psi;",[Char]
"\x03A8")
  ,(BS
"psi;",[Char]
"\x03C8")
  ,(BS
"puncsp;",[Char]
"\x2008")
  ,(BS
"Qfr;",[Char]
"\xD835\xDD14")
  ,(BS
"qfr;",[Char]
"\xD835\xDD2E")
  ,(BS
"qint;",[Char]
"\x2A0C")
  ,(BS
"Qopf;",[Char]
"\x211A")
  ,(BS
"qopf;",[Char]
"\xD835\xDD62")
  ,(BS
"qprime;",[Char]
"\x2057")
  ,(BS
"Qscr;",[Char]
"\xD835\xDCAC")
  ,(BS
"qscr;",[Char]
"\xD835\xDCC6")
  ,(BS
"quaternions;",[Char]
"\x210D")
  ,(BS
"quatint;",[Char]
"\x2A16")
  ,(BS
"quest;",[Char]
"\x003F")
  ,(BS
"questeq;",[Char]
"\x225F")
  ,(BS
"QUOT",[Char]
"\x0022")
  ,(BS
"quot",[Char]
"\x0022")
  ,(BS
"QUOT;",[Char]
"\x0022")
  ,(BS
"quot;",[Char]
"\x0022")
  ,(BS
"rAarr;",[Char]
"\x21DB")
  ,(BS
"race;",[Char]
"\x223D\x0331")
  ,(BS
"Racute;",[Char]
"\x0154")
  ,(BS
"racute;",[Char]
"\x0155")
  ,(BS
"radic;",[Char]
"\x221A")
  ,(BS
"raemptyv;",[Char]
"\x29B3")
  ,(BS
"rang;",[Char]
"\x27E9")
  ,(BS
"Rang;",[Char]
"\x27EB")
  ,(BS
"rangd;",[Char]
"\x2992")
  ,(BS
"range;",[Char]
"\x29A5")
  ,(BS
"rangle;",[Char]
"\x27E9")
  ,(BS
"raquo",[Char]
"\x00BB")
  ,(BS
"raquo;",[Char]
"\x00BB")
  ,(BS
"rarr;",[Char]
"\x2192")
  ,(BS
"Rarr;",[Char]
"\x21A0")
  ,(BS
"rArr;",[Char]
"\x21D2")
  ,(BS
"rarrap;",[Char]
"\x2975")
  ,(BS
"rarrb;",[Char]
"\x21E5")
  ,(BS
"rarrbfs;",[Char]
"\x2920")
  ,(BS
"rarrc;",[Char]
"\x2933")
  ,(BS
"rarrfs;",[Char]
"\x291E")
  ,(BS
"rarrhk;",[Char]
"\x21AA")
  ,(BS
"rarrlp;",[Char]
"\x21AC")
  ,(BS
"rarrpl;",[Char]
"\x2945")
  ,(BS
"rarrsim;",[Char]
"\x2974")
  ,(BS
"rarrtl;",[Char]
"\x21A3")
  ,(BS
"Rarrtl;",[Char]
"\x2916")
  ,(BS
"rarrw;",[Char]
"\x219D")
  ,(BS
"ratail;",[Char]
"\x291A")
  ,(BS
"rAtail;",[Char]
"\x291C")
  ,(BS
"ratio;",[Char]
"\x2236")
  ,(BS
"rationals;",[Char]
"\x211A")
  ,(BS
"rbarr;",[Char]
"\x290D")
  ,(BS
"rBarr;",[Char]
"\x290F")
  ,(BS
"RBarr;",[Char]
"\x2910")
  ,(BS
"rbbrk;",[Char]
"\x2773")
  ,(BS
"rbrace;",[Char]
"\x007D")
  ,(BS
"rbrack;",[Char]
"\x005D")
  ,(BS
"rbrke;",[Char]
"\x298C")
  ,(BS
"rbrksld;",[Char]
"\x298E")
  ,(BS
"rbrkslu;",[Char]
"\x2990")
  ,(BS
"Rcaron;",[Char]
"\x0158")
  ,(BS
"rcaron;",[Char]
"\x0159")
  ,(BS
"Rcedil;",[Char]
"\x0156")
  ,(BS
"rcedil;",[Char]
"\x0157")
  ,(BS
"rceil;",[Char]
"\x2309")
  ,(BS
"rcub;",[Char]
"\x007D")
  ,(BS
"Rcy;",[Char]
"\x0420")
  ,(BS
"rcy;",[Char]
"\x0440")
  ,(BS
"rdca;",[Char]
"\x2937")
  ,(BS
"rdldhar;",[Char]
"\x2969")
  ,(BS
"rdquo;",[Char]
"\x201D")
  ,(BS
"rdquor;",[Char]
"\x201D")
  ,(BS
"rdsh;",[Char]
"\x21B3")
  ,(BS
"Re;",[Char]
"\x211C")
  ,(BS
"real;",[Char]
"\x211C")
  ,(BS
"realine;",[Char]
"\x211B")
  ,(BS
"realpart;",[Char]
"\x211C")
  ,(BS
"reals;",[Char]
"\x211D")
  ,(BS
"rect;",[Char]
"\x25AD")
  ,(BS
"REG",[Char]
"\x00AE")
  ,(BS
"reg",[Char]
"\x00AE")
  ,(BS
"REG;",[Char]
"\x00AE")
  ,(BS
"reg;",[Char]
"\x00AE")
  ,(BS
"ReverseElement;",[Char]
"\x220B")
  ,(BS
"ReverseEquilibrium;",[Char]
"\x21CB")
  ,(BS
"ReverseUpEquilibrium;",[Char]
"\x296F")
  ,(BS
"rfisht;",[Char]
"\x297D")
  ,(BS
"rfloor;",[Char]
"\x230B")
  ,(BS
"Rfr;",[Char]
"\x211C")
  ,(BS
"rfr;",[Char]
"\xD835\xDD2F")
  ,(BS
"rHar;",[Char]
"\x2964")
  ,(BS
"rhard;",[Char]
"\x21C1")
  ,(BS
"rharu;",[Char]
"\x21C0")
  ,(BS
"rharul;",[Char]
"\x296C")
  ,(BS
"Rho;",[Char]
"\x03A1")
  ,(BS
"rho;",[Char]
"\x03C1")
  ,(BS
"rhov;",[Char]
"\x03F1")
  ,(BS
"RightAngleBracket;",[Char]
"\x27E9")
  ,(BS
"RightArrow;",[Char]
"\x2192")
  ,(BS
"rightarrow;",[Char]
"\x2192")
  ,(BS
"Rightarrow;",[Char]
"\x21D2")
  ,(BS
"RightArrowBar;",[Char]
"\x21E5")
  ,(BS
"RightArrowLeftArrow;",[Char]
"\x21C4")
  ,(BS
"rightarrowtail;",[Char]
"\x21A3")
  ,(BS
"RightCeiling;",[Char]
"\x2309")
  ,(BS
"RightDoubleBracket;",[Char]
"\x27E7")
  ,(BS
"RightDownTeeVector;",[Char]
"\x295D")
  ,(BS
"RightDownVector;",[Char]
"\x21C2")
  ,(BS
"RightDownVectorBar;",[Char]
"\x2955")
  ,(BS
"RightFloor;",[Char]
"\x230B")
  ,(BS
"rightharpoondown;",[Char]
"\x21C1")
  ,(BS
"rightharpoonup;",[Char]
"\x21C0")
  ,(BS
"rightleftarrows;",[Char]
"\x21C4")
  ,(BS
"rightleftharpoons;",[Char]
"\x21CC")
  ,(BS
"rightrightarrows;",[Char]
"\x21C9")
  ,(BS
"rightsquigarrow;",[Char]
"\x219D")
  ,(BS
"RightTee;",[Char]
"\x22A2")
  ,(BS
"RightTeeArrow;",[Char]
"\x21A6")
  ,(BS
"RightTeeVector;",[Char]
"\x295B")
  ,(BS
"rightthreetimes;",[Char]
"\x22CC")
  ,(BS
"RightTriangle;",[Char]
"\x22B3")
  ,(BS
"RightTriangleBar;",[Char]
"\x29D0")
  ,(BS
"RightTriangleEqual;",[Char]
"\x22B5")
  ,(BS
"RightUpDownVector;",[Char]
"\x294F")
  ,(BS
"RightUpTeeVector;",[Char]
"\x295C")
  ,(BS
"RightUpVector;",[Char]
"\x21BE")
  ,(BS
"RightUpVectorBar;",[Char]
"\x2954")
  ,(BS
"RightVector;",[Char]
"\x21C0")
  ,(BS
"RightVectorBar;",[Char]
"\x2953")
  ,(BS
"ring;",[Char]
"\x02DA")
  ,(BS
"risingdotseq;",[Char]
"\x2253")
  ,(BS
"rlarr;",[Char]
"\x21C4")
  ,(BS
"rlhar;",[Char]
"\x21CC")
  ,(BS
"rlm;",[Char]
"\x200F")
  ,(BS
"rmoust;",[Char]
"\x23B1")
  ,(BS
"rmoustache;",[Char]
"\x23B1")
  ,(BS
"rnmid;",[Char]
"\x2AEE")
  ,(BS
"roang;",[Char]
"\x27ED")
  ,(BS
"roarr;",[Char]
"\x21FE")
  ,(BS
"robrk;",[Char]
"\x27E7")
  ,(BS
"ropar;",[Char]
"\x2986")
  ,(BS
"Ropf;",[Char]
"\x211D")
  ,(BS
"ropf;",[Char]
"\xD835\xDD63")
  ,(BS
"roplus;",[Char]
"\x2A2E")
  ,(BS
"rotimes;",[Char]
"\x2A35")
  ,(BS
"RoundImplies;",[Char]
"\x2970")
  ,(BS
"rpar;",[Char]
"\x0029")
  ,(BS
"rpargt;",[Char]
"\x2994")
  ,(BS
"rppolint;",[Char]
"\x2A12")
  ,(BS
"rrarr;",[Char]
"\x21C9")
  ,(BS
"Rrightarrow;",[Char]
"\x21DB")
  ,(BS
"rsaquo;",[Char]
"\x203A")
  ,(BS
"Rscr;",[Char]
"\x211B")
  ,(BS
"rscr;",[Char]
"\xD835\xDCC7")
  ,(BS
"Rsh;",[Char]
"\x21B1")
  ,(BS
"rsh;",[Char]
"\x21B1")
  ,(BS
"rsqb;",[Char]
"\x005D")
  ,(BS
"rsquo;",[Char]
"\x2019")
  ,(BS
"rsquor;",[Char]
"\x2019")
  ,(BS
"rthree;",[Char]
"\x22CC")
  ,(BS
"rtimes;",[Char]
"\x22CA")
  ,(BS
"rtri;",[Char]
"\x25B9")
  ,(BS
"rtrie;",[Char]
"\x22B5")
  ,(BS
"rtrif;",[Char]
"\x25B8")
  ,(BS
"rtriltri;",[Char]
"\x29CE")
  ,(BS
"RuleDelayed;",[Char]
"\x29F4")
  ,(BS
"ruluhar;",[Char]
"\x2968")
  ,(BS
"rx;",[Char]
"\x211E")
  ,(BS
"Sacute;",[Char]
"\x015A")
  ,(BS
"sacute;",[Char]
"\x015B")
  ,(BS
"sbquo;",[Char]
"\x201A")
  ,(BS
"sc;",[Char]
"\x227B")
  ,(BS
"Sc;",[Char]
"\x2ABC")
  ,(BS
"scap;",[Char]
"\x2AB8")
  ,(BS
"Scaron;",[Char]
"\x0160")
  ,(BS
"scaron;",[Char]
"\x0161")
  ,(BS
"sccue;",[Char]
"\x227D")
  ,(BS
"sce;",[Char]
"\x2AB0")
  ,(BS
"scE;",[Char]
"\x2AB4")
  ,(BS
"Scedil;",[Char]
"\x015E")
  ,(BS
"scedil;",[Char]
"\x015F")
  ,(BS
"Scirc;",[Char]
"\x015C")
  ,(BS
"scirc;",[Char]
"\x015D")
  ,(BS
"scnap;",[Char]
"\x2ABA")
  ,(BS
"scnE;",[Char]
"\x2AB6")
  ,(BS
"scnsim;",[Char]
"\x22E9")
  ,(BS
"scpolint;",[Char]
"\x2A13")
  ,(BS
"scsim;",[Char]
"\x227F")
  ,(BS
"Scy;",[Char]
"\x0421")
  ,(BS
"scy;",[Char]
"\x0441")
  ,(BS
"sdot;",[Char]
"\x22C5")
  ,(BS
"sdotb;",[Char]
"\x22A1")
  ,(BS
"sdote;",[Char]
"\x2A66")
  ,(BS
"searhk;",[Char]
"\x2925")
  ,(BS
"searr;",[Char]
"\x2198")
  ,(BS
"seArr;",[Char]
"\x21D8")
  ,(BS
"searrow;",[Char]
"\x2198")
  ,(BS
"sect",[Char]
"\x00A7")
  ,(BS
"sect;",[Char]
"\x00A7")
  ,(BS
"semi;",[Char]
"\x003B")
  ,(BS
"seswar;",[Char]
"\x2929")
  ,(BS
"setminus;",[Char]
"\x2216")
  ,(BS
"setmn;",[Char]
"\x2216")
  ,(BS
"sext;",[Char]
"\x2736")
  ,(BS
"Sfr;",[Char]
"\xD835\xDD16")
  ,(BS
"sfr;",[Char]
"\xD835\xDD30")
  ,(BS
"sfrown;",[Char]
"\x2322")
  ,(BS
"sharp;",[Char]
"\x266F")
  ,(BS
"SHCHcy;",[Char]
"\x0429")
  ,(BS
"shchcy;",[Char]
"\x0449")
  ,(BS
"SHcy;",[Char]
"\x0428")
  ,(BS
"shcy;",[Char]
"\x0448")
  ,(BS
"ShortDownArrow;",[Char]
"\x2193")
  ,(BS
"ShortLeftArrow;",[Char]
"\x2190")
  ,(BS
"shortmid;",[Char]
"\x2223")
  ,(BS
"shortparallel;",[Char]
"\x2225")
  ,(BS
"ShortRightArrow;",[Char]
"\x2192")
  ,(BS
"ShortUpArrow;",[Char]
"\x2191")
  ,(BS
"shy",[Char]
"\x00AD")
  ,(BS
"shy;",[Char]
"\x00AD")
  ,(BS
"Sigma;",[Char]
"\x03A3")
  ,(BS
"sigma;",[Char]
"\x03C3")
  ,(BS
"sigmaf;",[Char]
"\x03C2")
  ,(BS
"sigmav;",[Char]
"\x03C2")
  ,(BS
"sim;",[Char]
"\x223C")
  ,(BS
"simdot;",[Char]
"\x2A6A")
  ,(BS
"sime;",[Char]
"\x2243")
  ,(BS
"simeq;",[Char]
"\x2243")
  ,(BS
"simg;",[Char]
"\x2A9E")
  ,(BS
"simgE;",[Char]
"\x2AA0")
  ,(BS
"siml;",[Char]
"\x2A9D")
  ,(BS
"simlE;",[Char]
"\x2A9F")
  ,(BS
"simne;",[Char]
"\x2246")
  ,(BS
"simplus;",[Char]
"\x2A24")
  ,(BS
"simrarr;",[Char]
"\x2972")
  ,(BS
"slarr;",[Char]
"\x2190")
  ,(BS
"SmallCircle;",[Char]
"\x2218")
  ,(BS
"smallsetminus;",[Char]
"\x2216")
  ,(BS
"smashp;",[Char]
"\x2A33")
  ,(BS
"smeparsl;",[Char]
"\x29E4")
  ,(BS
"smid;",[Char]
"\x2223")
  ,(BS
"smile;",[Char]
"\x2323")
  ,(BS
"smt;",[Char]
"\x2AAA")
  ,(BS
"smte;",[Char]
"\x2AAC")
  ,(BS
"smtes;",[Char]
"\x2AAC\xFE00")
  ,(BS
"SOFTcy;",[Char]
"\x042C")
  ,(BS
"softcy;",[Char]
"\x044C")
  ,(BS
"sol;",[Char]
"\x002F")
  ,(BS
"solb;",[Char]
"\x29C4")
  ,(BS
"solbar;",[Char]
"\x233F")
  ,(BS
"Sopf;",[Char]
"\xD835\xDD4A")
  ,(BS
"sopf;",[Char]
"\xD835\xDD64")
  ,(BS
"spades;",[Char]
"\x2660")
  ,(BS
"spadesuit;",[Char]
"\x2660")
  ,(BS
"spar;",[Char]
"\x2225")
  ,(BS
"sqcap;",[Char]
"\x2293")
  ,(BS
"sqcaps;",[Char]
"\x2293\xFE00")
  ,(BS
"sqcup;",[Char]
"\x2294")
  ,(BS
"sqcups;",[Char]
"\x2294\xFE00")
  ,(BS
"Sqrt;",[Char]
"\x221A")
  ,(BS
"sqsub;",[Char]
"\x228F")
  ,(BS
"sqsube;",[Char]
"\x2291")
  ,(BS
"sqsubset;",[Char]
"\x228F")
  ,(BS
"sqsubseteq;",[Char]
"\x2291")
  ,(BS
"sqsup;",[Char]
"\x2290")
  ,(BS
"sqsupe;",[Char]
"\x2292")
  ,(BS
"sqsupset;",[Char]
"\x2290")
  ,(BS
"sqsupseteq;",[Char]
"\x2292")
  ,(BS
"squ;",[Char]
"\x25A1")
  ,(BS
"Square;",[Char]
"\x25A1")
  ,(BS
"square;",[Char]
"\x25A1")
  ,(BS
"SquareIntersection;",[Char]
"\x2293")
  ,(BS
"SquareSubset;",[Char]
"\x228F")
  ,(BS
"SquareSubsetEqual;",[Char]
"\x2291")
  ,(BS
"SquareSuperset;",[Char]
"\x2290")
  ,(BS
"SquareSupersetEqual;",[Char]
"\x2292")
  ,(BS
"SquareUnion;",[Char]
"\x2294")
  ,(BS
"squarf;",[Char]
"\x25AA")
  ,(BS
"squf;",[Char]
"\x25AA")
  ,(BS
"srarr;",[Char]
"\x2192")
  ,(BS
"Sscr;",[Char]
"\xD835\xDCAE")
  ,(BS
"sscr;",[Char]
"\xD835\xDCC8")
  ,(BS
"ssetmn;",[Char]
"\x2216")
  ,(BS
"ssmile;",[Char]
"\x2323")
  ,(BS
"sstarf;",[Char]
"\x22C6")
  ,(BS
"Star;",[Char]
"\x22C6")
  ,(BS
"star;",[Char]
"\x2606")
  ,(BS
"starf;",[Char]
"\x2605")
  ,(BS
"straightepsilon;",[Char]
"\x03F5")
  ,(BS
"straightphi;",[Char]
"\x03D5")
  ,(BS
"strns;",[Char]
"\x00AF")
  ,(BS
"sub;",[Char]
"\x2282")
  ,(BS
"Sub;",[Char]
"\x22D0")
  ,(BS
"subdot;",[Char]
"\x2ABD")
  ,(BS
"sube;",[Char]
"\x2286")
  ,(BS
"subE;",[Char]
"\x2AC5")
  ,(BS
"subedot;",[Char]
"\x2AC3")
  ,(BS
"submult;",[Char]
"\x2AC1")
  ,(BS
"subne;",[Char]
"\x228A")
  ,(BS
"subnE;",[Char]
"\x2ACB")
  ,(BS
"subplus;",[Char]
"\x2ABF")
  ,(BS
"subrarr;",[Char]
"\x2979")
  ,(BS
"subset;",[Char]
"\x2282")
  ,(BS
"Subset;",[Char]
"\x22D0")
  ,(BS
"subseteq;",[Char]
"\x2286")
  ,(BS
"subseteqq;",[Char]
"\x2AC5")
  ,(BS
"SubsetEqual;",[Char]
"\x2286")
  ,(BS
"subsetneq;",[Char]
"\x228A")
  ,(BS
"subsetneqq;",[Char]
"\x2ACB")
  ,(BS
"subsim;",[Char]
"\x2AC7")
  ,(BS
"subsub;",[Char]
"\x2AD5")
  ,(BS
"subsup;",[Char]
"\x2AD3")
  ,(BS
"succ;",[Char]
"\x227B")
  ,(BS
"succapprox;",[Char]
"\x2AB8")
  ,(BS
"succcurlyeq;",[Char]
"\x227D")
  ,(BS
"Succeeds;",[Char]
"\x227B")
  ,(BS
"SucceedsEqual;",[Char]
"\x2AB0")
  ,(BS
"SucceedsSlantEqual;",[Char]
"\x227D")
  ,(BS
"SucceedsTilde;",[Char]
"\x227F")
  ,(BS
"succeq;",[Char]
"\x2AB0")
  ,(BS
"succnapprox;",[Char]
"\x2ABA")
  ,(BS
"succneqq;",[Char]
"\x2AB6")
  ,(BS
"succnsim;",[Char]
"\x22E9")
  ,(BS
"succsim;",[Char]
"\x227F")
  ,(BS
"SuchThat;",[Char]
"\x220B")
  ,(BS
"Sum;",[Char]
"\x2211")
  ,(BS
"sum;",[Char]
"\x2211")
  ,(BS
"sung;",[Char]
"\x266A")
  ,(BS
"sup1",[Char]
"\x00B9")
  ,(BS
"sup1;",[Char]
"\x00B9")
  ,(BS
"sup2",[Char]
"\x00B2")
  ,(BS
"sup2;",[Char]
"\x00B2")
  ,(BS
"sup3",[Char]
"\x00B3")
  ,(BS
"sup3;",[Char]
"\x00B3")
  ,(BS
"sup;",[Char]
"\x2283")
  ,(BS
"Sup;",[Char]
"\x22D1")
  ,(BS
"supdot;",[Char]
"\x2ABE")
  ,(BS
"supdsub;",[Char]
"\x2AD8")
  ,(BS
"supe;",[Char]
"\x2287")
  ,(BS
"supE;",[Char]
"\x2AC6")
  ,(BS
"supedot;",[Char]
"\x2AC4")
  ,(BS
"Superset;",[Char]
"\x2283")
  ,(BS
"SupersetEqual;",[Char]
"\x2287")
  ,(BS
"suphsol;",[Char]
"\x27C9")
  ,(BS
"suphsub;",[Char]
"\x2AD7")
  ,(BS
"suplarr;",[Char]
"\x297B")
  ,(BS
"supmult;",[Char]
"\x2AC2")
  ,(BS
"supne;",[Char]
"\x228B")
  ,(BS
"supnE;",[Char]
"\x2ACC")
  ,(BS
"supplus;",[Char]
"\x2AC0")
  ,(BS
"supset;",[Char]
"\x2283")
  ,(BS
"Supset;",[Char]
"\x22D1")
  ,(BS
"supseteq;",[Char]
"\x2287")
  ,(BS
"supseteqq;",[Char]
"\x2AC6")
  ,(BS
"supsetneq;",[Char]
"\x228B")
  ,(BS
"supsetneqq;",[Char]
"\x2ACC")
  ,(BS
"supsim;",[Char]
"\x2AC8")
  ,(BS
"supsub;",[Char]
"\x2AD4")
  ,(BS
"supsup;",[Char]
"\x2AD6")
  ,(BS
"swarhk;",[Char]
"\x2926")
  ,(BS
"swarr;",[Char]
"\x2199")
  ,(BS
"swArr;",[Char]
"\x21D9")
  ,(BS
"swarrow;",[Char]
"\x2199")
  ,(BS
"swnwar;",[Char]
"\x292A")
  ,(BS
"szlig",[Char]
"\x00DF")
  ,(BS
"szlig;",[Char]
"\x00DF")
  ,(BS
"Tab;",[Char]
"\x0009")
  ,(BS
"target;",[Char]
"\x2316")
  ,(BS
"Tau;",[Char]
"\x03A4")
  ,(BS
"tau;",[Char]
"\x03C4")
  ,(BS
"tbrk;",[Char]
"\x23B4")
  ,(BS
"Tcaron;",[Char]
"\x0164")
  ,(BS
"tcaron;",[Char]
"\x0165")
  ,(BS
"Tcedil;",[Char]
"\x0162")
  ,(BS
"tcedil;",[Char]
"\x0163")
  ,(BS
"Tcy;",[Char]
"\x0422")
  ,(BS
"tcy;",[Char]
"\x0442")
  ,(BS
"tdot;",[Char]
"\x20DB")
  ,(BS
"telrec;",[Char]
"\x2315")
  ,(BS
"Tfr;",[Char]
"\xD835\xDD17")
  ,(BS
"tfr;",[Char]
"\xD835\xDD31")
  ,(BS
"there4;",[Char]
"\x2234")
  ,(BS
"Therefore;",[Char]
"\x2234")
  ,(BS
"therefore;",[Char]
"\x2234")
  ,(BS
"Theta;",[Char]
"\x0398")
  ,(BS
"theta;",[Char]
"\x03B8")
  ,(BS
"thetasym;",[Char]
"\x03D1")
  ,(BS
"thetav;",[Char]
"\x03D1")
  ,(BS
"thickapprox;",[Char]
"\x2248")
  ,(BS
"thicksim;",[Char]
"\x223C")
  ,(BS
"ThickSpace;",[Char]
"\x205F\x200A")
  ,(BS
"thinsp;",[Char]
"\x2009")
  ,(BS
"ThinSpace;",[Char]
"\x2009")
  ,(BS
"thkap;",[Char]
"\x2248")
  ,(BS
"thksim;",[Char]
"\x223C")
  ,(BS
"THORN",[Char]
"\x00DE")
  ,(BS
"thorn",[Char]
"\x00FE")
  ,(BS
"THORN;",[Char]
"\x00DE")
  ,(BS
"thorn;",[Char]
"\x00FE")
  ,(BS
"tilde;",[Char]
"\x02DC")
  ,(BS
"Tilde;",[Char]
"\x223C")
  ,(BS
"TildeEqual;",[Char]
"\x2243")
  ,(BS
"TildeFullEqual;",[Char]
"\x2245")
  ,(BS
"TildeTilde;",[Char]
"\x2248")
  ,(BS
"times",[Char]
"\x00D7")
  ,(BS
"times;",[Char]
"\x00D7")
  ,(BS
"timesb;",[Char]
"\x22A0")
  ,(BS
"timesbar;",[Char]
"\x2A31")
  ,(BS
"timesd;",[Char]
"\x2A30")
  ,(BS
"tint;",[Char]
"\x222D")
  ,(BS
"toea;",[Char]
"\x2928")
  ,(BS
"top;",[Char]
"\x22A4")
  ,(BS
"topbot;",[Char]
"\x2336")
  ,(BS
"topcir;",[Char]
"\x2AF1")
  ,(BS
"Topf;",[Char]
"\xD835\xDD4B")
  ,(BS
"topf;",[Char]
"\xD835\xDD65")
  ,(BS
"topfork;",[Char]
"\x2ADA")
  ,(BS
"tosa;",[Char]
"\x2929")
  ,(BS
"tprime;",[Char]
"\x2034")
  ,(BS
"TRADE;",[Char]
"\x2122")
  ,(BS
"trade;",[Char]
"\x2122")
  ,(BS
"triangle;",[Char]
"\x25B5")
  ,(BS
"triangledown;",[Char]
"\x25BF")
  ,(BS
"triangleleft;",[Char]
"\x25C3")
  ,(BS
"trianglelefteq;",[Char]
"\x22B4")
  ,(BS
"triangleq;",[Char]
"\x225C")
  ,(BS
"triangleright;",[Char]
"\x25B9")
  ,(BS
"trianglerighteq;",[Char]
"\x22B5")
  ,(BS
"tridot;",[Char]
"\x25EC")
  ,(BS
"trie;",[Char]
"\x225C")
  ,(BS
"triminus;",[Char]
"\x2A3A")
  ,(BS
"TripleDot;",[Char]
"\x20DB")
  ,(BS
"triplus;",[Char]
"\x2A39")
  ,(BS
"trisb;",[Char]
"\x29CD")
  ,(BS
"tritime;",[Char]
"\x2A3B")
  ,(BS
"trpezium;",[Char]
"\x23E2")
  ,(BS
"Tscr;",[Char]
"\xD835\xDCAF")
  ,(BS
"tscr;",[Char]
"\xD835\xDCC9")
  ,(BS
"TScy;",[Char]
"\x0426")
  ,(BS
"tscy;",[Char]
"\x0446")
  ,(BS
"TSHcy;",[Char]
"\x040B")
  ,(BS
"tshcy;",[Char]
"\x045B")
  ,(BS
"Tstrok;",[Char]
"\x0166")
  ,(BS
"tstrok;",[Char]
"\x0167")
  ,(BS
"twixt;",[Char]
"\x226C")
  ,(BS
"twoheadleftarrow;",[Char]
"\x219E")
  ,(BS
"twoheadrightarrow;",[Char]
"\x21A0")
  ,(BS
"Uacute",[Char]
"\x00DA")
  ,(BS
"uacute",[Char]
"\x00FA")
  ,(BS
"Uacute;",[Char]
"\x00DA")
  ,(BS
"uacute;",[Char]
"\x00FA")
  ,(BS
"uarr;",[Char]
"\x2191")
  ,(BS
"Uarr;",[Char]
"\x219F")
  ,(BS
"uArr;",[Char]
"\x21D1")
  ,(BS
"Uarrocir;",[Char]
"\x2949")
  ,(BS
"Ubrcy;",[Char]
"\x040E")
  ,(BS
"ubrcy;",[Char]
"\x045E")
  ,(BS
"Ubreve;",[Char]
"\x016C")
  ,(BS
"ubreve;",[Char]
"\x016D")
  ,(BS
"Ucirc",[Char]
"\x00DB")
  ,(BS
"ucirc",[Char]
"\x00FB")
  ,(BS
"Ucirc;",[Char]
"\x00DB")
  ,(BS
"ucirc;",[Char]
"\x00FB")
  ,(BS
"Ucy;",[Char]
"\x0423")
  ,(BS
"ucy;",[Char]
"\x0443")
  ,(BS
"udarr;",[Char]
"\x21C5")
  ,(BS
"Udblac;",[Char]
"\x0170")
  ,(BS
"udblac;",[Char]
"\x0171")
  ,(BS
"udhar;",[Char]
"\x296E")
  ,(BS
"ufisht;",[Char]
"\x297E")
  ,(BS
"Ufr;",[Char]
"\xD835\xDD18")
  ,(BS
"ufr;",[Char]
"\xD835\xDD32")
  ,(BS
"Ugrave",[Char]
"\x00D9")
  ,(BS
"ugrave",[Char]
"\x00F9")
  ,(BS
"Ugrave;",[Char]
"\x00D9")
  ,(BS
"ugrave;",[Char]
"\x00F9")
  ,(BS
"uHar;",[Char]
"\x2963")
  ,(BS
"uharl;",[Char]
"\x21BF")
  ,(BS
"uharr;",[Char]
"\x21BE")
  ,(BS
"uhblk;",[Char]
"\x2580")
  ,(BS
"ulcorn;",[Char]
"\x231C")
  ,(BS
"ulcorner;",[Char]
"\x231C")
  ,(BS
"ulcrop;",[Char]
"\x230F")
  ,(BS
"ultri;",[Char]
"\x25F8")
  ,(BS
"Umacr;",[Char]
"\x016A")
  ,(BS
"umacr;",[Char]
"\x016B")
  ,(BS
"uml",[Char]
"\x00A8")
  ,(BS
"uml;",[Char]
"\x00A8")
  ,(BS
"UnderBar;",[Char]
"\x005F")
  ,(BS
"UnderBrace;",[Char]
"\x23DF")
  ,(BS
"UnderBracket;",[Char]
"\x23B5")
  ,(BS
"UnderParenthesis;",[Char]
"\x23DD")
  ,(BS
"Union;",[Char]
"\x22C3")
  ,(BS
"UnionPlus;",[Char]
"\x228E")
  ,(BS
"Uogon;",[Char]
"\x0172")
  ,(BS
"uogon;",[Char]
"\x0173")
  ,(BS
"Uopf;",[Char]
"\xD835\xDD4C")
  ,(BS
"uopf;",[Char]
"\xD835\xDD66")
  ,(BS
"UpArrow;",[Char]
"\x2191")
  ,(BS
"uparrow;",[Char]
"\x2191")
  ,(BS
"Uparrow;",[Char]
"\x21D1")
  ,(BS
"UpArrowBar;",[Char]
"\x2912")
  ,(BS
"UpArrowDownArrow;",[Char]
"\x21C5")
  ,(BS
"UpDownArrow;",[Char]
"\x2195")
  ,(BS
"updownarrow;",[Char]
"\x2195")
  ,(BS
"Updownarrow;",[Char]
"\x21D5")
  ,(BS
"UpEquilibrium;",[Char]
"\x296E")
  ,(BS
"upharpoonleft;",[Char]
"\x21BF")
  ,(BS
"upharpoonright;",[Char]
"\x21BE")
  ,(BS
"uplus;",[Char]
"\x228E")
  ,(BS
"UpperLeftArrow;",[Char]
"\x2196")
  ,(BS
"UpperRightArrow;",[Char]
"\x2197")
  ,(BS
"upsi;",[Char]
"\x03C5")
  ,(BS
"Upsi;",[Char]
"\x03D2")
  ,(BS
"upsih;",[Char]
"\x03D2")
  ,(BS
"Upsilon;",[Char]
"\x03A5")
  ,(BS
"upsilon;",[Char]
"\x03C5")
  ,(BS
"UpTee;",[Char]
"\x22A5")
  ,(BS
"UpTeeArrow;",[Char]
"\x21A5")
  ,(BS
"upuparrows;",[Char]
"\x21C8")
  ,(BS
"urcorn;",[Char]
"\x231D")
  ,(BS
"urcorner;",[Char]
"\x231D")
  ,(BS
"urcrop;",[Char]
"\x230E")
  ,(BS
"Uring;",[Char]
"\x016E")
  ,(BS
"uring;",[Char]
"\x016F")
  ,(BS
"urtri;",[Char]
"\x25F9")
  ,(BS
"Uscr;",[Char]
"\xD835\xDCB0")
  ,(BS
"uscr;",[Char]
"\xD835\xDCCA")
  ,(BS
"utdot;",[Char]
"\x22F0")
  ,(BS
"Utilde;",[Char]
"\x0168")
  ,(BS
"utilde;",[Char]
"\x0169")
  ,(BS
"utri;",[Char]
"\x25B5")
  ,(BS
"utrif;",[Char]
"\x25B4")
  ,(BS
"uuarr;",[Char]
"\x21C8")
  ,(BS
"Uuml",[Char]
"\x00DC")
  ,(BS
"uuml",[Char]
"\x00FC")
  ,(BS
"Uuml;",[Char]
"\x00DC")
  ,(BS
"uuml;",[Char]
"\x00FC")
  ,(BS
"uwangle;",[Char]
"\x29A7")
  ,(BS
"vangrt;",[Char]
"\x299C")
  ,(BS
"varepsilon;",[Char]
"\x03F5")
  ,(BS
"varkappa;",[Char]
"\x03F0")
  ,(BS
"varnothing;",[Char]
"\x2205")
  ,(BS
"varphi;",[Char]
"\x03D5")
  ,(BS
"varpi;",[Char]
"\x03D6")
  ,(BS
"varpropto;",[Char]
"\x221D")
  ,(BS
"varr;",[Char]
"\x2195")
  ,(BS
"vArr;",[Char]
"\x21D5")
  ,(BS
"varrho;",[Char]
"\x03F1")
  ,(BS
"varsigma;",[Char]
"\x03C2")
  ,(BS
"varsubsetneq;",[Char]
"\x228A\xFE00")
  ,(BS
"varsubsetneqq;",[Char]
"\x2ACB\xFE00")
  ,(BS
"varsupsetneq;",[Char]
"\x228B\xFE00")
  ,(BS
"varsupsetneqq;",[Char]
"\x2ACC\xFE00")
  ,(BS
"vartheta;",[Char]
"\x03D1")
  ,(BS
"vartriangleleft;",[Char]
"\x22B2")
  ,(BS
"vartriangleright;",[Char]
"\x22B3")
  ,(BS
"vBar;",[Char]
"\x2AE8")
  ,(BS
"Vbar;",[Char]
"\x2AEB")
  ,(BS
"vBarv;",[Char]
"\x2AE9")
  ,(BS
"Vcy;",[Char]
"\x0412")
  ,(BS
"vcy;",[Char]
"\x0432")
  ,(BS
"vdash;",[Char]
"\x22A2")
  ,(BS
"vDash;",[Char]
"\x22A8")
  ,(BS
"Vdash;",[Char]
"\x22A9")
  ,(BS
"VDash;",[Char]
"\x22AB")
  ,(BS
"Vdashl;",[Char]
"\x2AE6")
  ,(BS
"vee;",[Char]
"\x2228")
  ,(BS
"Vee;",[Char]
"\x22C1")
  ,(BS
"veebar;",[Char]
"\x22BB")
  ,(BS
"veeeq;",[Char]
"\x225A")
  ,(BS
"vellip;",[Char]
"\x22EE")
  ,(BS
"verbar;",[Char]
"\x007C")
  ,(BS
"Verbar;",[Char]
"\x2016")
  ,(BS
"vert;",[Char]
"\x007C")
  ,(BS
"Vert;",[Char]
"\x2016")
  ,(BS
"VerticalBar;",[Char]
"\x2223")
  ,(BS
"VerticalLine;",[Char]
"\x007C")
  ,(BS
"VerticalSeparator;",[Char]
"\x2758")
  ,(BS
"VerticalTilde;",[Char]
"\x2240")
  ,(BS
"VeryThinSpace;",[Char]
"\x200A")
  ,(BS
"Vfr;",[Char]
"\xD835\xDD19")
  ,(BS
"vfr;",[Char]
"\xD835\xDD33")
  ,(BS
"vltri;",[Char]
"\x22B2")
  ,(BS
"vnsub;",[Char]
"\x2282\x20D2")
  ,(BS
"vnsup;",[Char]
"\x2283\x20D2")
  ,(BS
"Vopf;",[Char]
"\xD835\xDD4D")
  ,(BS
"vopf;",[Char]
"\xD835\xDD67")
  ,(BS
"vprop;",[Char]
"\x221D")
  ,(BS
"vrtri;",[Char]
"\x22B3")
  ,(BS
"Vscr;",[Char]
"\xD835\xDCB1")
  ,(BS
"vscr;",[Char]
"\xD835\xDCCB")
  ,(BS
"vsubne;",[Char]
"\x228A\xFE00")
  ,(BS
"vsubnE;",[Char]
"\x2ACB\xFE00")
  ,(BS
"vsupne;",[Char]
"\x228B\xFE00")
  ,(BS
"vsupnE;",[Char]
"\x2ACC\xFE00")
  ,(BS
"Vvdash;",[Char]
"\x22AA")
  ,(BS
"vzigzag;",[Char]
"\x299A")
  ,(BS
"Wcirc;",[Char]
"\x0174")
  ,(BS
"wcirc;",[Char]
"\x0175")
  ,(BS
"wedbar;",[Char]
"\x2A5F")
  ,(BS
"wedge;",[Char]
"\x2227")
  ,(BS
"Wedge;",[Char]
"\x22C0")
  ,(BS
"wedgeq;",[Char]
"\x2259")
  ,(BS
"weierp;",[Char]
"\x2118")
  ,(BS
"Wfr;",[Char]
"\xD835\xDD1A")
  ,(BS
"wfr;",[Char]
"\xD835\xDD34")
  ,(BS
"Wopf;",[Char]
"\xD835\xDD4E")
  ,(BS
"wopf;",[Char]
"\xD835\xDD68")
  ,(BS
"wp;",[Char]
"\x2118")
  ,(BS
"wr;",[Char]
"\x2240")
  ,(BS
"wreath;",[Char]
"\x2240")
  ,(BS
"Wscr;",[Char]
"\xD835\xDCB2")
  ,(BS
"wscr;",[Char]
"\xD835\xDCCC")
  ,(BS
"xcap;",[Char]
"\x22C2")
  ,(BS
"xcirc;",[Char]
"\x25EF")
  ,(BS
"xcup;",[Char]
"\x22C3")
  ,(BS
"xdtri;",[Char]
"\x25BD")
  ,(BS
"Xfr;",[Char]
"\xD835\xDD1B")
  ,(BS
"xfr;",[Char]
"\xD835\xDD35")
  ,(BS
"xharr;",[Char]
"\x27F7")
  ,(BS
"xhArr;",[Char]
"\x27FA")
  ,(BS
"Xi;",[Char]
"\x039E")
  ,(BS
"xi;",[Char]
"\x03BE")
  ,(BS
"xlarr;",[Char]
"\x27F5")
  ,(BS
"xlArr;",[Char]
"\x27F8")
  ,(BS
"xmap;",[Char]
"\x27FC")
  ,(BS
"xnis;",[Char]
"\x22FB")
  ,(BS
"xodot;",[Char]
"\x2A00")
  ,(BS
"Xopf;",[Char]
"\xD835\xDD4F")
  ,(BS
"xopf;",[Char]
"\xD835\xDD69")
  ,(BS
"xoplus;",[Char]
"\x2A01")
  ,(BS
"xotime;",[Char]
"\x2A02")
  ,(BS
"xrarr;",[Char]
"\x27F6")
  ,(BS
"xrArr;",[Char]
"\x27F9")
  ,(BS
"Xscr;",[Char]
"\xD835\xDCB3")
  ,(BS
"xscr;",[Char]
"\xD835\xDCCD")
  ,(BS
"xsqcup;",[Char]
"\x2A06")
  ,(BS
"xuplus;",[Char]
"\x2A04")
  ,(BS
"xutri;",[Char]
"\x25B3")
  ,(BS
"xvee;",[Char]
"\x22C1")
  ,(BS
"xwedge;",[Char]
"\x22C0")
  ,(BS
"Yacute",[Char]
"\x00DD")
  ,(BS
"yacute",[Char]
"\x00FD")
  ,(BS
"Yacute;",[Char]
"\x00DD")
  ,(BS
"yacute;",[Char]
"\x00FD")
  ,(BS
"YAcy;",[Char]
"\x042F")
  ,(BS
"yacy;",[Char]
"\x044F")
  ,(BS
"Ycirc;",[Char]
"\x0176")
  ,(BS
"ycirc;",[Char]
"\x0177")
  ,(BS
"Ycy;",[Char]
"\x042B")
  ,(BS
"ycy;",[Char]
"\x044B")
  ,(BS
"yen",[Char]
"\x00A5")
  ,(BS
"yen;",[Char]
"\x00A5")
  ,(BS
"Yfr;",[Char]
"\xD835\xDD1C")
  ,(BS
"yfr;",[Char]
"\xD835\xDD36")
  ,(BS
"YIcy;",[Char]
"\x0407")
  ,(BS
"yicy;",[Char]
"\x0457")
  ,(BS
"Yopf;",[Char]
"\xD835\xDD50")
  ,(BS
"yopf;",[Char]
"\xD835\xDD6A")
  ,(BS
"Yscr;",[Char]
"\xD835\xDCB4")
  ,(BS
"yscr;",[Char]
"\xD835\xDCCE")
  ,(BS
"YUcy;",[Char]
"\x042E")
  ,(BS
"yucy;",[Char]
"\x044E")
  ,(BS
"yuml",[Char]
"\x00FF")
  ,(BS
"yuml;",[Char]
"\x00FF")
  ,(BS
"Yuml;",[Char]
"\x0178")
  ,(BS
"Zacute;",[Char]
"\x0179")
  ,(BS
"zacute;",[Char]
"\x017A")
  ,(BS
"Zcaron;",[Char]
"\x017D")
  ,(BS
"zcaron;",[Char]
"\x017E")
  ,(BS
"Zcy;",[Char]
"\x0417")
  ,(BS
"zcy;",[Char]
"\x0437")
  ,(BS
"Zdot;",[Char]
"\x017B")
  ,(BS
"zdot;",[Char]
"\x017C")
  ,(BS
"zeetrf;",[Char]
"\x2128")
  ,(BS
"ZeroWidthSpace;",[Char]
"\x200B")
  ,(BS
"Zeta;",[Char]
"\x0396")
  ,(BS
"zeta;",[Char]
"\x03B6")
  ,(BS
"Zfr;",[Char]
"\x2128")
  ,(BS
"zfr;",[Char]
"\xD835\xDD37")
  ,(BS
"ZHcy;",[Char]
"\x0416")
  ,(BS
"zhcy;",[Char]
"\x0436")
  ,(BS
"zigrarr;",[Char]
"\x21DD")
  ,(BS
"Zopf;",[Char]
"\x2124")
  ,(BS
"zopf;",[Char]
"\xD835\xDD6B")
  ,(BS
"Zscr;",[Char]
"\xD835\xDCB5")
  ,(BS
"zscr;",[Char]
"\xD835\xDCCF")
  ,(BS
"zwj;",[Char]
"\x200D")
  ,(BS
"zwnj;",[Char]
"\x200C")]