├── .gitignore
├── Setup.hs
├── tests
├── Spec.hs
└── Text
│ └── HTML
│ ├── TreeSpec.hs
│ └── ParserSpec.hs
├── changelog.md
├── app
└── Main.hs
├── gen_entities.py
├── src
├── Data
│ └── Trie.hs
└── Text
│ └── HTML
│ ├── Tree.hs
│ ├── Parser.hs
│ └── Parser
│ └── Entities.hs
├── Microbench.hs
├── Benchmark.hs
├── LICENSE
├── README.mkd
├── html-parse.cabal
└── .github
└── workflows
└── haskell-ci.yml
/.gitignore:
--------------------------------------------------------------------------------
1 | *.hi
2 | *.o
3 | dist
4 | *.dump-*
5 |
--------------------------------------------------------------------------------
/Setup.hs:
--------------------------------------------------------------------------------
1 | import Distribution.Simple
2 | main = defaultMain
3 |
--------------------------------------------------------------------------------
/tests/Spec.hs:
--------------------------------------------------------------------------------
1 | {-# OPTIONS_GHC -F -pgmF hspec-discover #-}
2 |
--------------------------------------------------------------------------------
/changelog.md:
--------------------------------------------------------------------------------
1 | # Changelog for `html-parse`
2 |
3 | ## 0.2.2.0
4 |
5 | - Fix dropping of attributes in some cases (#27)
6 | - Fix parsing of unquoted attributes (#28)
7 |
8 | ## 0.2.1.0
9 |
10 | - Added support for decoding of character references (#18)
11 | - All self-closing elements are now recognized as such
12 |
13 | ## Earlier
14 |
15 | There be dragons.
16 |
--------------------------------------------------------------------------------
/app/Main.hs:
--------------------------------------------------------------------------------
1 | module Main where
2 |
3 | import Control.Monad
4 | import qualified Data.Text as T
5 | import qualified Data.Text.IO as T
6 | import Text.HTML.Parser
7 | import System.Environment
8 |
9 | main :: IO ()
10 | main = do
11 | files <- getArgs
12 | forM_ files $ \fname -> do
13 | t <- T.readFile fname
14 | print $ length $ parseTokens t
15 |
16 |
--------------------------------------------------------------------------------
/gen_entities.py:
--------------------------------------------------------------------------------
1 | #!/usr/bin/env python3
2 |
3 | """
4 | Converts entity WHATWG HTML5 entity summary into
5 | Text.HTML.Parser.Entities module.
6 |
7 | Usage:
8 |
9 | curl https://html.spec.whatwg.org/entities.json | python3 gen_entities.py > src/Text/HTML/Parser/Entities.hs
10 |
11 | """
12 |
13 | import sys
14 | import json
15 |
16 | entities = json.load(sys.stdin)
17 |
18 | def escape(details):
19 | return ''.join(f'\\x{cp:04x}' for cp in details['codepoints'])
20 |
21 | print('''
22 | {-# LANGUAGE OverloadedStrings #-}
23 |
24 | -- | N.B. This file is generated by @gen_entities.py@. Do not edit.
25 | module Text.HTML.Parser.Entities (entities) where
26 |
27 | import Data.Text (Text)
28 |
29 | entities :: [(Text, Text)]
30 | entities = [
31 | '''.strip())
32 | print(',\n'.join(
33 | f''' ("{name[1:-1]}", "{escape(details)}")'''
34 | for name, details in entities.items()
35 | ))
36 | print(' ]')
37 |
--------------------------------------------------------------------------------
/src/Data/Trie.hs:
--------------------------------------------------------------------------------
1 | module Data.Trie
2 | ( Trie
3 | , singleton, fromList
4 | , terminal, step
5 | ) where
6 |
7 | import Control.Applicative
8 |
9 | import qualified Data.Map.Strict as M
10 |
11 | data Trie k v
12 | = TrieNode !(Maybe v) !(M.Map k (Trie k v))
13 |
14 | instance Ord k => Monoid (Trie k v) where
15 | mempty = TrieNode Nothing M.empty
16 |
17 | instance Ord k => Semigroup (Trie k v) where
18 | TrieNode v0 ys0 <> TrieNode v1 ys1 =
19 | TrieNode (v1 <|> v0) (M.unionWith (<>) ys0 ys1)
20 |
21 | singleton :: Ord k => [k] -> v -> Trie k v
22 | singleton = go
23 | where
24 | go [] v = TrieNode (Just v) M.empty
25 | go (x:xs) v = TrieNode Nothing (M.singleton x (go xs v))
26 |
27 | fromList :: Ord k => [([k], v)] -> Trie k v
28 | fromList = foldMap (uncurry singleton)
29 |
30 | terminal :: Trie k v -> Maybe v
31 | terminal (TrieNode v _) = v
32 |
33 | step :: Ord k => k -> Trie k v -> Trie k v
34 | step k (TrieNode _ xs) = M.findWithDefault mempty k xs
35 |
--------------------------------------------------------------------------------
/Microbench.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE MagicHash #-}
2 | {-# LANGUAGE OverloadedStrings #-}
3 |
4 | import GHC.Exts
5 | import Data.Char
6 | import qualified Data.Text as T
7 | import Data.Attoparsec.Text
8 | import Criterion.Main
9 | import Prelude hiding (take, takeWhile)
10 |
11 | isAsciiAlpha1 :: Char -> Bool
12 | isAsciiAlpha1 c = isAsciiLower c || isAsciiUpper c
13 |
14 | isAsciiAlpha2 :: Char -> Bool
15 | isAsciiAlpha2 (C# c) =
16 | tagToEnum# ( ((c `geChar#` 'A'#) `andI#` (c `leChar#` 'Z'#))
17 | `orI#` ((c `geChar#` 'a'#) `andI#` (c `leChar#` 'z'#)) )
18 |
19 | main :: IO ()
20 | main = defaultMain
21 | [ bench "Text isAsciiAlpha1"
22 | $ whnf (T.length . T.takeWhile isAsciiAlpha1) testString
23 | , bench "Text isAsciiAlpha2"
24 | $ whnf (T.length . T.takeWhile isAsciiAlpha2) testString
25 |
26 | , bench "Attoparsec isAsciiAlpha1"
27 | $ whnf (parseOnly (T.length <$> takeWhile isAsciiAlpha1)) testString
28 | , bench "Attoparsec isAsciiAlpha2"
29 | $ whnf (parseOnly (T.length <$> takeWhile isAsciiAlpha2)) testString
30 | ]
31 |
32 | testString :: T.Text
33 | testString = T.replicate 10 "helloworldthisisarelativelylongstring"
34 |
--------------------------------------------------------------------------------
/Benchmark.hs:
--------------------------------------------------------------------------------
1 | import Criterion.Main
2 | import qualified Data.Text.IO as TIO
3 | import Control.DeepSeq
4 | import qualified Text.HTML.TagSoup as Soup
5 | import qualified Text.HTML.Parser as Me
6 |
7 | main :: IO ()
8 | main = do
9 | t <- TIO.readFile "test.html"
10 | defaultMain
11 | [ bgroup "Forced"
12 | [ bench "tagsoup fast Text" $ nf (Soup.parseTagsOptions Soup.parseOptionsFast) t
13 | , bench "tagsoup normal Text" $ nf (Soup.parseTagsOptions Soup.parseOptions) t
14 | , bench "html-parser" $ nf Me.parseTokens t
15 | ]
16 | , bgroup "length"
17 | [ bench "tagsoup fast Text" $ whnf (length . Soup.parseTagsOptions Soup.parseOptionsFast) t
18 | , bench "tagsoup normal Text" $ whnf (length . Soup.parseTagsOptions Soup.parseOptions) t
19 | , bench "html-parser" $ whnf (length . Me.parseTokens) t
20 | ]
21 | ]
22 |
23 | instance NFData t => NFData (Soup.Tag t) where
24 | rnf (Soup.TagOpen t attrs) = rnf t `seq` rnf attrs `seq` ()
25 | rnf (Soup.TagClose t) = rnf t `seq` ()
26 | rnf (Soup.TagText t) = rnf t `seq` ()
27 | rnf (Soup.TagComment t) = rnf t `seq` ()
28 | rnf (Soup.TagWarning t) = rnf t `seq` ()
29 | rnf (Soup.TagPosition _ _) = ()
30 |
--------------------------------------------------------------------------------
/tests/Text/HTML/TreeSpec.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE FlexibleInstances #-}
2 | {-# LANGUAGE OverloadedStrings #-}
3 | {-# LANGUAGE ScopedTypeVariables #-}
4 |
5 | {-# OPTIONS_GHC -Wall -Werror -fno-warn-orphans #-}
6 |
7 | module Text.HTML.TreeSpec
8 | where
9 |
10 | import Control.Applicative
11 | import Data.Tree
12 | import Test.Hspec
13 | import Test.QuickCheck
14 | import Test.QuickCheck.Instances ()
15 | import Text.HTML.Parser
16 | import Text.HTML.ParserSpec
17 | import Text.HTML.Tree
18 | import Prelude
19 |
20 |
21 | arbitraryTokenForest :: Gen (Forest Token)
22 | arbitraryTokenForest = listOf arbitraryTokenTree
23 |
24 | arbitraryTokenTree :: Gen (Tree Token)
25 | arbitraryTokenTree = oneof
26 | [ Node <$> validClosingOpen <*> scale (`div` 5) arbitraryTokenForest
27 | , Node <$> validNonClosingOpen <*> pure []
28 | , Node <$> validFlat <*> pure []
29 | ]
30 |
31 |
32 | validNonClosingOpen :: Gen Token
33 | validNonClosingOpen = TagOpen <$> elements nonClosing <*> arbitrary
34 |
35 | validClosingOpen :: Gen Token
36 | validClosingOpen = do
37 | n <- validXmlTagName
38 | let n' = if n `elem` nonClosing then "_" else n
39 | TagOpen n' <$> arbitrary
40 |
41 |
42 | spec :: Spec
43 | spec = do
44 | it "parseTokenForests and renderTokenForest are inverses"
45 | . property . forAllShrink arbitraryTokenForest shrink $
46 | \forest -> tokensToForest (tokensFromForest forest) `shouldBe` Right forest
47 |
--------------------------------------------------------------------------------
/LICENSE:
--------------------------------------------------------------------------------
1 | Copyright (c) 2016, Ben Gamari
2 |
3 | All rights reserved.
4 |
5 | Redistribution and use in source and binary forms, with or without
6 | modification, are permitted provided that the following conditions are met:
7 |
8 | * Redistributions of source code must retain the above copyright
9 | notice, this list of conditions and the following disclaimer.
10 |
11 | * Redistributions in binary form must reproduce the above
12 | copyright notice, this list of conditions and the following
13 | disclaimer in the documentation and/or other materials provided
14 | with the distribution.
15 |
16 | * Neither the name of Ben Gamari nor the names of other
17 | contributors may be used to endorse or promote products derived
18 | from this software without specific prior written permission.
19 |
20 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21 | "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22 | LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
23 | A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
24 | OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
25 | SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
26 | LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
27 | DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
28 | THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
29 | (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
30 | OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
31 |
--------------------------------------------------------------------------------
/README.mkd:
--------------------------------------------------------------------------------
1 | # html-parse
2 |
3 | `html-parse` is an efficient, reasonably robust HTML tokenizer based on the
4 | HTML5 tokenization
5 | [specification](https://html.spec.whatwg.org/multipage/syntax.html#tokenization).
6 | The parser is written using the fast `attoparsec` parsing library and can
7 | exposes both a native `attoparsec` `Parser` as well as convenience functions for
8 | lazily parsing token streams out of strict and lazy `Text` values.
9 |
10 | For instance,
11 | ```haskell
12 | >>> parseTokens "
"
13 | [TagOpen "div" [],TagOpen "h1" [],ContentText "Hello World",TagClose "h1",TagSelfClose "br" [],TagOpen "p" [Attr "class" "widget"],ContentText "Example!",TagClose "p",TagClose "div"]
14 | ```
15 |
16 | ## Performance
17 |
18 | Here are some typical performance numbers taken from parsing a fairly
19 | long [Wikipedia article](https://en.wikipedia.org/wiki/New_York_City),
20 | ```
21 | benchmarking Forced/tagsoup fast Text
22 | time 171.2 ms (166.4 ms .. 177.3 ms)
23 | 0.999 R² (0.997 R² .. 1.000 R²)
24 | mean 171.9 ms (169.4 ms .. 173.2 ms)
25 | std dev 2.516 ms (1.104 ms .. 3.558 ms)
26 | variance introduced by outliers: 12% (moderately inflated)
27 |
28 | benchmarking Forced/tagsoup normal Text
29 | time 176.9 ms (167.3 ms .. 188.5 ms)
30 | 0.998 R² (0.994 R² .. 1.000 R²)
31 | mean 180.7 ms (177.5 ms .. 183.7 ms)
32 | std dev 4.246 ms (2.316 ms .. 5.803 ms)
33 | variance introduced by outliers: 14% (moderately inflated)
34 |
35 | benchmarking Forced/html-parser
36 | time 20.88 ms (20.60 ms .. 21.25 ms)
37 | 0.999 R² (0.998 R² .. 0.999 R²)
38 | mean 20.99 ms (20.81 ms .. 21.20 ms)
39 | std dev 446.1 μs (336.4 μs .. 596.2 μs)
40 | ```
41 |
--------------------------------------------------------------------------------
/src/Text/HTML/Tree.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE OverloadedStrings #-}
2 | {-# LANGUAGE ViewPatterns #-}
3 |
4 | module Text.HTML.Tree
5 | ( -- * Constructing forests
6 | tokensToForest
7 | , ParseTokenForestError(..), PStack(..)
8 | , nonClosing
9 | -- * Deconstructing forests
10 | , tokensFromForest
11 | , tokensFromTree
12 | ) where
13 |
14 | import Data.Monoid
15 | import Data.Text (Text)
16 | import Data.Tree
17 | import Prelude
18 |
19 | import Text.HTML.Parser
20 |
21 | -- | construct a 'Forest' from a 'Token' list.
22 | --
23 | -- This code correctly handles void elements. Void elements are required to have a start tag and must not have an end tag. See 'nonClosing'.
24 | --
25 | -- This code does __not__ correctly handle optional tags. It assumes all optional start and end tags are present.
26 | --
27 | --
28 | tokensToForest :: [Token] -> Either ParseTokenForestError (Forest Token)
29 | tokensToForest = f (PStack [] [])
30 | where
31 | f (PStack ss []) [] = Right (reverse ss)
32 | f pstack [] = Left $ ParseTokenForestErrorBracketMismatch pstack Nothing
33 | f pstack (t : ts) = case t of
34 | TagOpen n _ -> if n `elem` nonClosing
35 | then f (pushFlatSibling t pstack) ts
36 | else f (pushParent t pstack) ts
37 | TagSelfClose {} -> f (pushFlatSibling t pstack) ts
38 | TagClose n -> (`f` ts) =<< popParent n pstack
39 | ContentChar _ -> f (pushFlatSibling t pstack) ts
40 | ContentText _ -> f (pushFlatSibling t pstack) ts
41 | Comment _ -> f (pushFlatSibling t pstack) ts
42 | Doctype _ -> f (pushFlatSibling t pstack) ts
43 |
44 | -- | void elements which must not have an end tag
45 | --
46 | -- This list does not include the obsolete @\@ and @\@ elements.
47 | --
48 | -- @ nonClosing = ["br", "hr", "img", "meta", "area", "base", "col", "embed", "input", "link", "param", "source", "track", "wbr"] @
49 | --
50 | --
51 | nonClosing :: [Text]
52 | nonClosing = ["br", "hr", "img", "meta", "area", "base", "col", "embed", "input", "link", "param", "source", "track", "wbr"]
53 |
54 | data ParseTokenForestError =
55 | ParseTokenForestErrorBracketMismatch PStack (Maybe Token)
56 | deriving (Eq, Show)
57 |
58 | data PStack = PStack
59 | { _pstackToplevelSiblings :: Forest Token
60 | , _pstackParents :: [(Token, Forest Token)]
61 | }
62 | deriving (Eq, Show)
63 |
64 | pushParent :: Token -> PStack -> PStack
65 | pushParent t (PStack ss ps) = PStack [] ((t, ss) : ps)
66 |
67 | popParent :: TagName -> PStack -> Either ParseTokenForestError PStack
68 | popParent n (PStack ss ((p@(TagOpen n' _), ss') : ps))
69 | | n == n' = Right $ PStack (Node p (reverse ss) : ss') ps
70 | popParent n pstack
71 | = Left $ ParseTokenForestErrorBracketMismatch pstack (Just $ TagClose n)
72 |
73 | pushFlatSibling :: Token -> PStack -> PStack
74 | pushFlatSibling t (PStack ss ps) = PStack (Node t [] : ss) ps
75 |
76 | -- | convert a 'Forest' of 'Token' into a list of 'Token'.
77 | --
78 | -- This code correctly handles void elements. Void elements are required to have a start tag and must not have an end tag. See 'nonClosing'.
79 | tokensFromForest :: Forest Token -> [Token]
80 | tokensFromForest = mconcat . fmap tokensFromTree
81 |
82 | -- | convert a 'Tree' of 'Token' into a list of 'Token'.
83 | --
84 | -- This code correctly handles void elements. Void elements are required to have a start tag and must not have an end tag. See 'nonClosing'.
85 | tokensFromTree :: Tree Token -> [Token]
86 | tokensFromTree (Node o@(TagOpen n _) ts) | n `notElem` nonClosing
87 | = [o] <> tokensFromForest ts <> [TagClose n]
88 | tokensFromTree (Node t [])
89 | = [t]
90 | tokensFromTree _
91 | = error "renderTokenTree: leaf node with children."
92 |
--------------------------------------------------------------------------------
/html-parse.cabal:
--------------------------------------------------------------------------------
1 | name: html-parse
2 | version: 0.2.2.0
3 | synopsis: A high-performance HTML tokenizer
4 | description:
5 | This package provides a fast and reasonably robust HTML5 tokenizer built
6 | upon the @attoparsec@ library. The parsing strategy is based upon the HTML5
7 | parsing specification with few deviations.
8 | .
9 | For instance,
10 | .
11 | >>> parseTokens ""
12 | [TagOpen "div" [],
13 | TagOpen "h1" [Attr "class" "widget"],
14 | ContentText "Hello World",
15 | TagClose "h1",
16 | TagSelfClose "br" []]
17 | .
18 | The package targets similar use-cases to the venerable @tagsoup@ library,
19 | but is significantly more efficient, achieving parsing speeds of over 80
20 | megabytes per second on modern hardware and typical web documents.
21 | Here are some typical performance numbers taken from parsing a Wikipedia
22 | article of moderate length:
23 | .
24 | @
25 | benchmarking Forced/tagsoup fast Text
26 | time 186.1 ms (175.3 ms .. 194.6 ms)
27 | 0.999 R² (0.995 R² .. 1.000 R²)
28 | mean 191.7 ms (188.9 ms .. 198.3 ms)
29 | std dev 5.053 ms (1.092 ms .. 6.809 ms)
30 | variance introduced by outliers: 14% (moderately inflated)
31 | .
32 | benchmarking Forced/tagsoup normal Text
33 | time 189.7 ms (182.8 ms .. 197.7 ms)
34 | 0.999 R² (0.998 R² .. 1.000 R²)
35 | mean 196.5 ms (193.1 ms .. 202.1 ms)
36 | std dev 5.481 ms (2.141 ms .. 7.383 ms)
37 | variance introduced by outliers: 14% (moderately inflated)
38 | .
39 | benchmarking Forced/html-parser
40 | time 15.81 ms (15.75 ms .. 15.89 ms)
41 | 1.000 R² (1.000 R² .. 1.000 R²)
42 | mean 15.72 ms (15.66 ms .. 15.77 ms)
43 | std dev 140.9 μs (113.6 μs .. 174.5 μs)
44 | @
45 |
46 | homepage: http://github.com/bgamari/html-parse
47 | license: BSD3
48 | license-file: LICENSE
49 | author: Ben Gamari
50 | maintainer: ben@smart-cactus.org
51 | copyright: (c) 2016 Ben Gamari
52 | category: Text
53 | build-type: Simple
54 | cabal-version: >=1.10
55 | tested-with: GHC==8.10.7,
56 | GHC==9.0.2,
57 | GHC==9.2.5,
58 | GHC==9.4.5,
59 | GHC==9.6.7,
60 | GHC==9.8.4,
61 | GHC==9.10.1,
62 | GHC==9.12.1
63 | extra-source-files: changelog.md
64 |
65 |
66 | source-repository head
67 | type: git
68 | location: https://github.com/bgamari/html-parse
69 |
70 | library
71 | exposed-modules: Text.HTML.Parser, Text.HTML.Tree
72 | other-modules: Text.HTML.Parser.Entities, Data.Trie
73 | ghc-options: -Wall
74 | hs-source-dirs: src
75 | other-extensions: OverloadedStrings, DeriveGeneric
76 | build-depends: base >=4.7 && <4.22,
77 | deepseq >=1.3 && <1.6,
78 | attoparsec >=0.13 && <0.15,
79 | text >=1.2 && <2.2,
80 | containers >=0.5 && <0.9
81 | default-language: Haskell2010
82 |
83 | benchmark bench
84 | type: exitcode-stdio-1.0
85 | main-is: Benchmark.hs
86 | other-extensions: OverloadedStrings, DeriveGeneric
87 | build-depends: base,
88 | deepseq,
89 | attoparsec,
90 | text,
91 | tagsoup >= 0.13,
92 | criterion >= 1.1,
93 | html-parse
94 | default-language: Haskell2010
95 |
96 | test-suite spec
97 | type: exitcode-stdio-1.0
98 | hs-source-dirs: tests
99 | main-is: Spec.hs
100 | other-modules: Text.HTML.ParserSpec, Text.HTML.TreeSpec
101 | ghc-options: -Wall -with-rtsopts=-T
102 | build-tool-depends: hspec-discover:hspec-discover
103 | build-depends: base,
104 | containers,
105 | hspec,
106 | hspec-discover,
107 | html-parse,
108 | QuickCheck,
109 | quickcheck-instances,
110 | string-conversions,
111 | text
112 | default-language: Haskell2010
113 |
114 | -- For performance characterisation during optimisation
115 | executable html-parse-length
116 | main-is: app/Main.hs
117 | buildable: False
118 | build-depends: base,
119 | html-parse,
120 | text
121 | default-language: Haskell2010
122 |
--------------------------------------------------------------------------------
/tests/Text/HTML/ParserSpec.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE GADTs #-}
2 | {-# LANGUAGE GeneralizedNewtypeDeriving #-}
3 | {-# LANGUAGE OverloadedStrings #-}
4 | {-# LANGUAGE ScopedTypeVariables #-}
5 | {-# LANGUAGE ViewPatterns #-}
6 |
7 | {-# OPTIONS_GHC -Wall -Werror -fno-warn-orphans -fno-warn-unused-imports #-}
8 |
9 | module Text.HTML.ParserSpec
10 | where
11 |
12 | import Control.Applicative
13 | import Data.Monoid
14 | import Data.List ((\\))
15 | import qualified Data.Text as T
16 | import qualified Data.Text.Lazy as TL
17 | import qualified Data.Text.Lazy.Builder as B
18 | import Test.Hspec
19 | import Test.QuickCheck
20 | import Test.QuickCheck.Instances ()
21 | import Text.HTML.Parser
22 |
23 |
24 | instance Arbitrary Token where
25 | arbitrary = oneof [validOpen, validClose, validFlat]
26 |
27 | shrink (TagOpen n as) = TagOpen n <$> shrink as
28 | shrink (TagSelfClose n as) = TagSelfClose n <$> shrink as
29 | shrink (TagClose _) = []
30 | shrink (ContentText _) = []
31 | shrink (ContentChar _) = []
32 | shrink (Comment b) = Comment . B.fromText <$> (shrink . TL.toStrict . B.toLazyText $ b)
33 | shrink (Doctype t) = Doctype <$> shrink t
34 |
35 | instance Arbitrary Attr where
36 | arbitrary = Attr <$> validXmlAttrName <*> validXmlAttrValue
37 | shrink (Attr k v) = Attr <$> shrink k <*> shrink v
38 |
39 | validOpen :: Gen Token
40 | validOpen = TagOpen <$> validXmlTagName <*> arbitrary
41 |
42 | validClose :: Gen Token
43 | validClose = TagClose <$> validXmlTagName
44 |
45 | validFlat :: Gen Token
46 | validFlat = oneof
47 | [ TagSelfClose <$> validXmlTagName <*> arbitrary
48 | , ContentChar <$> validXmlChar
49 | , ContentText <$> validXmlText
50 | , Comment . B.fromText <$> validXmlCommentText
51 | , Doctype <$> validXmlText
52 | ]
53 |
54 | -- FIXME: sometimes it is allowed to use '<' as text token, and we don't test that yet. (whether we
55 | -- like this choice or not, we may want to follow the standard here.) (same in tag names, attr
56 | -- names). We also avoid '&' since this may produce spurious character references.
57 | validXmlChar :: Gen Char
58 | validXmlChar = elements (['\x20'..'\x7E'] \\ "\x09\x0a\x0c &/<>")
59 |
60 | validXmlText :: Gen T.Text
61 | validXmlText = T.pack <$> sized (`maxListOf` validXmlChar)
62 |
63 | validXmlTagName :: Gen T.Text
64 | validXmlTagName = do
65 | initchar <- elements $ ['a'..'z'] <> ['A'..'Z']
66 | thenchars <- sized (`maxListOf` elements (['\x20'..'\x7E'] \\ "\x09\x0a\x0c &/<>"))
67 | pure . T.pack $ initchar : thenchars
68 |
69 | validXmlAttrName :: Gen T.Text
70 | validXmlAttrName = do
71 | initchar <- elements $ ['a'..'z'] <> ['A'..'Z']
72 | thenchars <- sized (`maxListOf` elements (['\x20'..'\x7E'] \\ "\x09\x0a\x0c /=<>\x00"))
73 | pure . T.pack $ initchar : thenchars
74 |
75 | -- FIXME: not sure if @Attr "key" "\""@ should be parseable, but it's not, so we don't test it.
76 | validXmlAttrValue :: Gen T.Text
77 | validXmlAttrValue = do
78 | T.pack <$> sized (`maxListOf` elements (['\x20'..'\x7E'] \\ "\x09\x0a\x0c /=<>\x00\""))
79 |
80 | -- FIXME: i think this should be 'validXmlChar', but that will fail the test suite.
81 | validXmlCommentText :: Gen T.Text
82 | validXmlCommentText = do
83 | T.pack <$> sized (`maxListOf` elements (['\x20'..'\x7E'] \\ "\x09\x0a\x0c /=<>\x00\"-"))
84 |
85 | maxListOf :: Int -> Gen a -> Gen [a]
86 | maxListOf n g = take n <$> listOf g
87 |
88 | parsesTo :: String -> [Token] -> Spec
89 | parsesTo str expected = do
90 | it ("parses " <> str) $ do
91 | parseTokens (T.pack str) `shouldBe` expected
92 |
93 | spec :: Spec
94 | spec = do
95 | it "parseTokens and renderTokens are inverse" . property . forAllShrink arbitrary shrink $
96 | \(canonicalizeTokens -> tokens)
97 | -> (canonicalizeTokens . parseTokens . TL.toStrict . renderTokens $ tokens) `shouldBe` tokens
98 |
99 | it "canonicalizeTokens is idempotent" . property . forAllShrink arbitrary shrink $
100 | \tokens
101 | -> canonicalizeTokens tokens `shouldBe` canonicalizeTokens (canonicalizeTokens tokens)
102 |
103 | describe "regression tests" $ do
104 | describe "parseTokens" $ do
105 | it "works on `
Heading
`" $ do
106 | parseTokens "
Heading
" `shouldBe` [TagOpen "h1" [], ContentText "Heading", TagClose "h1"]
107 | it "terminates on truncated tags" $ do
108 | parseTokens "19 -167.44
" `shouldBe` [Comment " 3. Change Banner "]
111 | it "parses commented tag correctly" $ do
112 | parseTokens ""]
411 | (Doctype t) -> [""]
412 |
413 | -- | See 'renderAttr'.
414 | renderAttrs :: [Attr] -> Text
415 | renderAttrs = T.unwords . fmap renderAttr . reverse
416 |
417 | -- | Does not escape quotation in attribute values!
418 | renderAttr :: Attr -> Text
419 | renderAttr (Attr k v) = mconcat [k, "=\"", v, "\""]
420 |
421 | -- | Meld neighoring 'ContentChar' and 'ContentText'
422 | -- constructors together and drops empty text elements.
423 | canonicalizeTokens :: [Token] -> [Token]
424 | canonicalizeTokens = filter (/= ContentText "") . meldTextTokens
425 |
426 | meldTextTokens :: [Token] -> [Token]
427 | meldTextTokens = concatTexts . fmap charToText
428 | where
429 | charToText (ContentChar c) = ContentText (T.singleton c)
430 | charToText t = t
431 |
432 | concatTexts = \case
433 | (ContentText t : ContentText t' : ts) -> concatTexts $ ContentText (t <> t') : ts
434 | (t : ts) -> t : concatTexts ts
435 | [] -> []
436 |
--------------------------------------------------------------------------------
/src/Text/HTML/Parser/Entities.hs:
--------------------------------------------------------------------------------
1 | {-# LANGUAGE OverloadedStrings #-}
2 |
3 | -- | N.B. This file is generated by @gen_entities.py@. Do not edit.
4 | module Text.HTML.Parser.Entities (entities) where
5 |
6 | import Data.Text (Text)
7 |
8 | entities :: [(Text, Text)]
9 | entities = [
10 | ("AEli", "\x00c6"),
11 | ("AElig", "\x00c6"),
12 | ("AM", "\x0026"),
13 | ("AMP", "\x0026"),
14 | ("Aacut", "\x00c1"),
15 | ("Aacute", "\x00c1"),
16 | ("Abreve", "\x0102"),
17 | ("Acir", "\x00c2"),
18 | ("Acirc", "\x00c2"),
19 | ("Acy", "\x0410"),
20 | ("Afr", "\x1d504"),
21 | ("Agrav", "\x00c0"),
22 | ("Agrave", "\x00c0"),
23 | ("Alpha", "\x0391"),
24 | ("Amacr", "\x0100"),
25 | ("And", "\x2a53"),
26 | ("Aogon", "\x0104"),
27 | ("Aopf", "\x1d538"),
28 | ("ApplyFunction", "\x2061"),
29 | ("Arin", "\x00c5"),
30 | ("Aring", "\x00c5"),
31 | ("Ascr", "\x1d49c"),
32 | ("Assign", "\x2254"),
33 | ("Atild", "\x00c3"),
34 | ("Atilde", "\x00c3"),
35 | ("Aum", "\x00c4"),
36 | ("Auml", "\x00c4"),
37 | ("Backslash", "\x2216"),
38 | ("Barv", "\x2ae7"),
39 | ("Barwed", "\x2306"),
40 | ("Bcy", "\x0411"),
41 | ("Because", "\x2235"),
42 | ("Bernoullis", "\x212c"),
43 | ("Beta", "\x0392"),
44 | ("Bfr", "\x1d505"),
45 | ("Bopf", "\x1d539"),
46 | ("Breve", "\x02d8"),
47 | ("Bscr", "\x212c"),
48 | ("Bumpeq", "\x224e"),
49 | ("CHcy", "\x0427"),
50 | ("COP", "\x00a9"),
51 | ("COPY", "\x00a9"),
52 | ("Cacute", "\x0106"),
53 | ("Cap", "\x22d2"),
54 | ("CapitalDifferentialD", "\x2145"),
55 | ("Cayleys", "\x212d"),
56 | ("Ccaron", "\x010c"),
57 | ("Ccedi", "\x00c7"),
58 | ("Ccedil", "\x00c7"),
59 | ("Ccirc", "\x0108"),
60 | ("Cconint", "\x2230"),
61 | ("Cdot", "\x010a"),
62 | ("Cedilla", "\x00b8"),
63 | ("CenterDot", "\x00b7"),
64 | ("Cfr", "\x212d"),
65 | ("Chi", "\x03a7"),
66 | ("CircleDot", "\x2299"),
67 | ("CircleMinus", "\x2296"),
68 | ("CirclePlus", "\x2295"),
69 | ("CircleTimes", "\x2297"),
70 | ("ClockwiseContourIntegral", "\x2232"),
71 | ("CloseCurlyDoubleQuote", "\x201d"),
72 | ("CloseCurlyQuote", "\x2019"),
73 | ("Colon", "\x2237"),
74 | ("Colone", "\x2a74"),
75 | ("Congruent", "\x2261"),
76 | ("Conint", "\x222f"),
77 | ("ContourIntegral", "\x222e"),
78 | ("Copf", "\x2102"),
79 | ("Coproduct", "\x2210"),
80 | ("CounterClockwiseContourIntegral", "\x2233"),
81 | ("Cross", "\x2a2f"),
82 | ("Cscr", "\x1d49e"),
83 | ("Cup", "\x22d3"),
84 | ("CupCap", "\x224d"),
85 | ("DD", "\x2145"),
86 | ("DDotrahd", "\x2911"),
87 | ("DJcy", "\x0402"),
88 | ("DScy", "\x0405"),
89 | ("DZcy", "\x040f"),
90 | ("Dagger", "\x2021"),
91 | ("Darr", "\x21a1"),
92 | ("Dashv", "\x2ae4"),
93 | ("Dcaron", "\x010e"),
94 | ("Dcy", "\x0414"),
95 | ("Del", "\x2207"),
96 | ("Delta", "\x0394"),
97 | ("Dfr", "\x1d507"),
98 | ("DiacriticalAcute", "\x00b4"),
99 | ("DiacriticalDot", "\x02d9"),
100 | ("DiacriticalDoubleAcute", "\x02dd"),
101 | ("DiacriticalGrave", "\x0060"),
102 | ("DiacriticalTilde", "\x02dc"),
103 | ("Diamond", "\x22c4"),
104 | ("DifferentialD", "\x2146"),
105 | ("Dopf", "\x1d53b"),
106 | ("Dot", "\x00a8"),
107 | ("DotDot", "\x20dc"),
108 | ("DotEqual", "\x2250"),
109 | ("DoubleContourIntegral", "\x222f"),
110 | ("DoubleDot", "\x00a8"),
111 | ("DoubleDownArrow", "\x21d3"),
112 | ("DoubleLeftArrow", "\x21d0"),
113 | ("DoubleLeftRightArrow", "\x21d4"),
114 | ("DoubleLeftTee", "\x2ae4"),
115 | ("DoubleLongLeftArrow", "\x27f8"),
116 | ("DoubleLongLeftRightArrow", "\x27fa"),
117 | ("DoubleLongRightArrow", "\x27f9"),
118 | ("DoubleRightArrow", "\x21d2"),
119 | ("DoubleRightTee", "\x22a8"),
120 | ("DoubleUpArrow", "\x21d1"),
121 | ("DoubleUpDownArrow", "\x21d5"),
122 | ("DoubleVerticalBar", "\x2225"),
123 | ("DownArrow", "\x2193"),
124 | ("DownArrowBar", "\x2913"),
125 | ("DownArrowUpArrow", "\x21f5"),
126 | ("DownBreve", "\x0311"),
127 | ("DownLeftRightVector", "\x2950"),
128 | ("DownLeftTeeVector", "\x295e"),
129 | ("DownLeftVector", "\x21bd"),
130 | ("DownLeftVectorBar", "\x2956"),
131 | ("DownRightTeeVector", "\x295f"),
132 | ("DownRightVector", "\x21c1"),
133 | ("DownRightVectorBar", "\x2957"),
134 | ("DownTee", "\x22a4"),
135 | ("DownTeeArrow", "\x21a7"),
136 | ("Downarrow", "\x21d3"),
137 | ("Dscr", "\x1d49f"),
138 | ("Dstrok", "\x0110"),
139 | ("ENG", "\x014a"),
140 | ("ET", "\x00d0"),
141 | ("ETH", "\x00d0"),
142 | ("Eacut", "\x00c9"),
143 | ("Eacute", "\x00c9"),
144 | ("Ecaron", "\x011a"),
145 | ("Ecir", "\x00ca"),
146 | ("Ecirc", "\x00ca"),
147 | ("Ecy", "\x042d"),
148 | ("Edot", "\x0116"),
149 | ("Efr", "\x1d508"),
150 | ("Egrav", "\x00c8"),
151 | ("Egrave", "\x00c8"),
152 | ("Element", "\x2208"),
153 | ("Emacr", "\x0112"),
154 | ("EmptySmallSquare", "\x25fb"),
155 | ("EmptyVerySmallSquare", "\x25ab"),
156 | ("Eogon", "\x0118"),
157 | ("Eopf", "\x1d53c"),
158 | ("Epsilon", "\x0395"),
159 | ("Equal", "\x2a75"),
160 | ("EqualTilde", "\x2242"),
161 | ("Equilibrium", "\x21cc"),
162 | ("Escr", "\x2130"),
163 | ("Esim", "\x2a73"),
164 | ("Eta", "\x0397"),
165 | ("Eum", "\x00cb"),
166 | ("Euml", "\x00cb"),
167 | ("Exists", "\x2203"),
168 | ("ExponentialE", "\x2147"),
169 | ("Fcy", "\x0424"),
170 | ("Ffr", "\x1d509"),
171 | ("FilledSmallSquare", "\x25fc"),
172 | ("FilledVerySmallSquare", "\x25aa"),
173 | ("Fopf", "\x1d53d"),
174 | ("ForAll", "\x2200"),
175 | ("Fouriertrf", "\x2131"),
176 | ("Fscr", "\x2131"),
177 | ("GJcy", "\x0403"),
178 | ("G", "\x003e"),
179 | ("GT", "\x003e"),
180 | ("Gamma", "\x0393"),
181 | ("Gammad", "\x03dc"),
182 | ("Gbreve", "\x011e"),
183 | ("Gcedil", "\x0122"),
184 | ("Gcirc", "\x011c"),
185 | ("Gcy", "\x0413"),
186 | ("Gdot", "\x0120"),
187 | ("Gfr", "\x1d50a"),
188 | ("Gg", "\x22d9"),
189 | ("Gopf", "\x1d53e"),
190 | ("GreaterEqual", "\x2265"),
191 | ("GreaterEqualLess", "\x22db"),
192 | ("GreaterFullEqual", "\x2267"),
193 | ("GreaterGreater", "\x2aa2"),
194 | ("GreaterLess", "\x2277"),
195 | ("GreaterSlantEqual", "\x2a7e"),
196 | ("GreaterTilde", "\x2273"),
197 | ("Gscr", "\x1d4a2"),
198 | ("Gt", "\x226b"),
199 | ("HARDcy", "\x042a"),
200 | ("Hacek", "\x02c7"),
201 | ("Hat", "\x005e"),
202 | ("Hcirc", "\x0124"),
203 | ("Hfr", "\x210c"),
204 | ("HilbertSpace", "\x210b"),
205 | ("Hopf", "\x210d"),
206 | ("HorizontalLine", "\x2500"),
207 | ("Hscr", "\x210b"),
208 | ("Hstrok", "\x0126"),
209 | ("HumpDownHump", "\x224e"),
210 | ("HumpEqual", "\x224f"),
211 | ("IEcy", "\x0415"),
212 | ("IJlig", "\x0132"),
213 | ("IOcy", "\x0401"),
214 | ("Iacut", "\x00cd"),
215 | ("Iacute", "\x00cd"),
216 | ("Icir", "\x00ce"),
217 | ("Icirc", "\x00ce"),
218 | ("Icy", "\x0418"),
219 | ("Idot", "\x0130"),
220 | ("Ifr", "\x2111"),
221 | ("Igrav", "\x00cc"),
222 | ("Igrave", "\x00cc"),
223 | ("Im", "\x2111"),
224 | ("Imacr", "\x012a"),
225 | ("ImaginaryI", "\x2148"),
226 | ("Implies", "\x21d2"),
227 | ("Int", "\x222c"),
228 | ("Integral", "\x222b"),
229 | ("Intersection", "\x22c2"),
230 | ("InvisibleComma", "\x2063"),
231 | ("InvisibleTimes", "\x2062"),
232 | ("Iogon", "\x012e"),
233 | ("Iopf", "\x1d540"),
234 | ("Iota", "\x0399"),
235 | ("Iscr", "\x2110"),
236 | ("Itilde", "\x0128"),
237 | ("Iukcy", "\x0406"),
238 | ("Ium", "\x00cf"),
239 | ("Iuml", "\x00cf"),
240 | ("Jcirc", "\x0134"),
241 | ("Jcy", "\x0419"),
242 | ("Jfr", "\x1d50d"),
243 | ("Jopf", "\x1d541"),
244 | ("Jscr", "\x1d4a5"),
245 | ("Jsercy", "\x0408"),
246 | ("Jukcy", "\x0404"),
247 | ("KHcy", "\x0425"),
248 | ("KJcy", "\x040c"),
249 | ("Kappa", "\x039a"),
250 | ("Kcedil", "\x0136"),
251 | ("Kcy", "\x041a"),
252 | ("Kfr", "\x1d50e"),
253 | ("Kopf", "\x1d542"),
254 | ("Kscr", "\x1d4a6"),
255 | ("LJcy", "\x0409"),
256 | ("L", "\x003c"),
257 | ("LT", "\x003c"),
258 | ("Lacute", "\x0139"),
259 | ("Lambda", "\x039b"),
260 | ("Lang", "\x27ea"),
261 | ("Laplacetrf", "\x2112"),
262 | ("Larr", "\x219e"),
263 | ("Lcaron", "\x013d"),
264 | ("Lcedil", "\x013b"),
265 | ("Lcy", "\x041b"),
266 | ("LeftAngleBracket", "\x27e8"),
267 | ("LeftArrow", "\x2190"),
268 | ("LeftArrowBar", "\x21e4"),
269 | ("LeftArrowRightArrow", "\x21c6"),
270 | ("LeftCeiling", "\x2308"),
271 | ("LeftDoubleBracket", "\x27e6"),
272 | ("LeftDownTeeVector", "\x2961"),
273 | ("LeftDownVector", "\x21c3"),
274 | ("LeftDownVectorBar", "\x2959"),
275 | ("LeftFloor", "\x230a"),
276 | ("LeftRightArrow", "\x2194"),
277 | ("LeftRightVector", "\x294e"),
278 | ("LeftTee", "\x22a3"),
279 | ("LeftTeeArrow", "\x21a4"),
280 | ("LeftTeeVector", "\x295a"),
281 | ("LeftTriangle", "\x22b2"),
282 | ("LeftTriangleBar", "\x29cf"),
283 | ("LeftTriangleEqual", "\x22b4"),
284 | ("LeftUpDownVector", "\x2951"),
285 | ("LeftUpTeeVector", "\x2960"),
286 | ("LeftUpVector", "\x21bf"),
287 | ("LeftUpVectorBar", "\x2958"),
288 | ("LeftVector", "\x21bc"),
289 | ("LeftVectorBar", "\x2952"),
290 | ("Leftarrow", "\x21d0"),
291 | ("Leftrightarrow", "\x21d4"),
292 | ("LessEqualGreater", "\x22da"),
293 | ("LessFullEqual", "\x2266"),
294 | ("LessGreater", "\x2276"),
295 | ("LessLess", "\x2aa1"),
296 | ("LessSlantEqual", "\x2a7d"),
297 | ("LessTilde", "\x2272"),
298 | ("Lfr", "\x1d50f"),
299 | ("Ll", "\x22d8"),
300 | ("Lleftarrow", "\x21da"),
301 | ("Lmidot", "\x013f"),
302 | ("LongLeftArrow", "\x27f5"),
303 | ("LongLeftRightArrow", "\x27f7"),
304 | ("LongRightArrow", "\x27f6"),
305 | ("Longleftarrow", "\x27f8"),
306 | ("Longleftrightarrow", "\x27fa"),
307 | ("Longrightarrow", "\x27f9"),
308 | ("Lopf", "\x1d543"),
309 | ("LowerLeftArrow", "\x2199"),
310 | ("LowerRightArrow", "\x2198"),
311 | ("Lscr", "\x2112"),
312 | ("Lsh", "\x21b0"),
313 | ("Lstrok", "\x0141"),
314 | ("Lt", "\x226a"),
315 | ("Map", "\x2905"),
316 | ("Mcy", "\x041c"),
317 | ("MediumSpace", "\x205f"),
318 | ("Mellintrf", "\x2133"),
319 | ("Mfr", "\x1d510"),
320 | ("MinusPlus", "\x2213"),
321 | ("Mopf", "\x1d544"),
322 | ("Mscr", "\x2133"),
323 | ("Mu", "\x039c"),
324 | ("NJcy", "\x040a"),
325 | ("Nacute", "\x0143"),
326 | ("Ncaron", "\x0147"),
327 | ("Ncedil", "\x0145"),
328 | ("Ncy", "\x041d"),
329 | ("NegativeMediumSpace", "\x200b"),
330 | ("NegativeThickSpace", "\x200b"),
331 | ("NegativeThinSpace", "\x200b"),
332 | ("NegativeVeryThinSpace", "\x200b"),
333 | ("NestedGreaterGreater", "\x226b"),
334 | ("NestedLessLess", "\x226a"),
335 | ("NewLine", "\x000a"),
336 | ("Nfr", "\x1d511"),
337 | ("NoBreak", "\x2060"),
338 | ("NonBreakingSpace", "\x00a0"),
339 | ("Nopf", "\x2115"),
340 | ("Not", "\x2aec"),
341 | ("NotCongruent", "\x2262"),
342 | ("NotCupCap", "\x226d"),
343 | ("NotDoubleVerticalBar", "\x2226"),
344 | ("NotElement", "\x2209"),
345 | ("NotEqual", "\x2260"),
346 | ("NotEqualTilde", "\x2242\x0338"),
347 | ("NotExists", "\x2204"),
348 | ("NotGreater", "\x226f"),
349 | ("NotGreaterEqual", "\x2271"),
350 | ("NotGreaterFullEqual", "\x2267\x0338"),
351 | ("NotGreaterGreater", "\x226b\x0338"),
352 | ("NotGreaterLess", "\x2279"),
353 | ("NotGreaterSlantEqual", "\x2a7e\x0338"),
354 | ("NotGreaterTilde", "\x2275"),
355 | ("NotHumpDownHump", "\x224e\x0338"),
356 | ("NotHumpEqual", "\x224f\x0338"),
357 | ("NotLeftTriangle", "\x22ea"),
358 | ("NotLeftTriangleBar", "\x29cf\x0338"),
359 | ("NotLeftTriangleEqual", "\x22ec"),
360 | ("NotLess", "\x226e"),
361 | ("NotLessEqual", "\x2270"),
362 | ("NotLessGreater", "\x2278"),
363 | ("NotLessLess", "\x226a\x0338"),
364 | ("NotLessSlantEqual", "\x2a7d\x0338"),
365 | ("NotLessTilde", "\x2274"),
366 | ("NotNestedGreaterGreater", "\x2aa2\x0338"),
367 | ("NotNestedLessLess", "\x2aa1\x0338"),
368 | ("NotPrecedes", "\x2280"),
369 | ("NotPrecedesEqual", "\x2aaf\x0338"),
370 | ("NotPrecedesSlantEqual", "\x22e0"),
371 | ("NotReverseElement", "\x220c"),
372 | ("NotRightTriangle", "\x22eb"),
373 | ("NotRightTriangleBar", "\x29d0\x0338"),
374 | ("NotRightTriangleEqual", "\x22ed"),
375 | ("NotSquareSubset", "\x228f\x0338"),
376 | ("NotSquareSubsetEqual", "\x22e2"),
377 | ("NotSquareSuperset", "\x2290\x0338"),
378 | ("NotSquareSupersetEqual", "\x22e3"),
379 | ("NotSubset", "\x2282\x20d2"),
380 | ("NotSubsetEqual", "\x2288"),
381 | ("NotSucceeds", "\x2281"),
382 | ("NotSucceedsEqual", "\x2ab0\x0338"),
383 | ("NotSucceedsSlantEqual", "\x22e1"),
384 | ("NotSucceedsTilde", "\x227f\x0338"),
385 | ("NotSuperset", "\x2283\x20d2"),
386 | ("NotSupersetEqual", "\x2289"),
387 | ("NotTilde", "\x2241"),
388 | ("NotTildeEqual", "\x2244"),
389 | ("NotTildeFullEqual", "\x2247"),
390 | ("NotTildeTilde", "\x2249"),
391 | ("NotVerticalBar", "\x2224"),
392 | ("Nscr", "\x1d4a9"),
393 | ("Ntild", "\x00d1"),
394 | ("Ntilde", "\x00d1"),
395 | ("Nu", "\x039d"),
396 | ("OElig", "\x0152"),
397 | ("Oacut", "\x00d3"),
398 | ("Oacute", "\x00d3"),
399 | ("Ocir", "\x00d4"),
400 | ("Ocirc", "\x00d4"),
401 | ("Ocy", "\x041e"),
402 | ("Odblac", "\x0150"),
403 | ("Ofr", "\x1d512"),
404 | ("Ograv", "\x00d2"),
405 | ("Ograve", "\x00d2"),
406 | ("Omacr", "\x014c"),
407 | ("Omega", "\x03a9"),
408 | ("Omicron", "\x039f"),
409 | ("Oopf", "\x1d546"),
410 | ("OpenCurlyDoubleQuote", "\x201c"),
411 | ("OpenCurlyQuote", "\x2018"),
412 | ("Or", "\x2a54"),
413 | ("Oscr", "\x1d4aa"),
414 | ("Oslas", "\x00d8"),
415 | ("Oslash", "\x00d8"),
416 | ("Otild", "\x00d5"),
417 | ("Otilde", "\x00d5"),
418 | ("Otimes", "\x2a37"),
419 | ("Oum", "\x00d6"),
420 | ("Ouml", "\x00d6"),
421 | ("OverBar", "\x203e"),
422 | ("OverBrace", "\x23de"),
423 | ("OverBracket", "\x23b4"),
424 | ("OverParenthesis", "\x23dc"),
425 | ("PartialD", "\x2202"),
426 | ("Pcy", "\x041f"),
427 | ("Pfr", "\x1d513"),
428 | ("Phi", "\x03a6"),
429 | ("Pi", "\x03a0"),
430 | ("PlusMinus", "\x00b1"),
431 | ("Poincareplane", "\x210c"),
432 | ("Popf", "\x2119"),
433 | ("Pr", "\x2abb"),
434 | ("Precedes", "\x227a"),
435 | ("PrecedesEqual", "\x2aaf"),
436 | ("PrecedesSlantEqual", "\x227c"),
437 | ("PrecedesTilde", "\x227e"),
438 | ("Prime", "\x2033"),
439 | ("Product", "\x220f"),
440 | ("Proportion", "\x2237"),
441 | ("Proportional", "\x221d"),
442 | ("Pscr", "\x1d4ab"),
443 | ("Psi", "\x03a8"),
444 | ("QUO", "\x0022"),
445 | ("QUOT", "\x0022"),
446 | ("Qfr", "\x1d514"),
447 | ("Qopf", "\x211a"),
448 | ("Qscr", "\x1d4ac"),
449 | ("RBarr", "\x2910"),
450 | ("RE", "\x00ae"),
451 | ("REG", "\x00ae"),
452 | ("Racute", "\x0154"),
453 | ("Rang", "\x27eb"),
454 | ("Rarr", "\x21a0"),
455 | ("Rarrtl", "\x2916"),
456 | ("Rcaron", "\x0158"),
457 | ("Rcedil", "\x0156"),
458 | ("Rcy", "\x0420"),
459 | ("Re", "\x211c"),
460 | ("ReverseElement", "\x220b"),
461 | ("ReverseEquilibrium", "\x21cb"),
462 | ("ReverseUpEquilibrium", "\x296f"),
463 | ("Rfr", "\x211c"),
464 | ("Rho", "\x03a1"),
465 | ("RightAngleBracket", "\x27e9"),
466 | ("RightArrow", "\x2192"),
467 | ("RightArrowBar", "\x21e5"),
468 | ("RightArrowLeftArrow", "\x21c4"),
469 | ("RightCeiling", "\x2309"),
470 | ("RightDoubleBracket", "\x27e7"),
471 | ("RightDownTeeVector", "\x295d"),
472 | ("RightDownVector", "\x21c2"),
473 | ("RightDownVectorBar", "\x2955"),
474 | ("RightFloor", "\x230b"),
475 | ("RightTee", "\x22a2"),
476 | ("RightTeeArrow", "\x21a6"),
477 | ("RightTeeVector", "\x295b"),
478 | ("RightTriangle", "\x22b3"),
479 | ("RightTriangleBar", "\x29d0"),
480 | ("RightTriangleEqual", "\x22b5"),
481 | ("RightUpDownVector", "\x294f"),
482 | ("RightUpTeeVector", "\x295c"),
483 | ("RightUpVector", "\x21be"),
484 | ("RightUpVectorBar", "\x2954"),
485 | ("RightVector", "\x21c0"),
486 | ("RightVectorBar", "\x2953"),
487 | ("Rightarrow", "\x21d2"),
488 | ("Ropf", "\x211d"),
489 | ("RoundImplies", "\x2970"),
490 | ("Rrightarrow", "\x21db"),
491 | ("Rscr", "\x211b"),
492 | ("Rsh", "\x21b1"),
493 | ("RuleDelayed", "\x29f4"),
494 | ("SHCHcy", "\x0429"),
495 | ("SHcy", "\x0428"),
496 | ("SOFTcy", "\x042c"),
497 | ("Sacute", "\x015a"),
498 | ("Sc", "\x2abc"),
499 | ("Scaron", "\x0160"),
500 | ("Scedil", "\x015e"),
501 | ("Scirc", "\x015c"),
502 | ("Scy", "\x0421"),
503 | ("Sfr", "\x1d516"),
504 | ("ShortDownArrow", "\x2193"),
505 | ("ShortLeftArrow", "\x2190"),
506 | ("ShortRightArrow", "\x2192"),
507 | ("ShortUpArrow", "\x2191"),
508 | ("Sigma", "\x03a3"),
509 | ("SmallCircle", "\x2218"),
510 | ("Sopf", "\x1d54a"),
511 | ("Sqrt", "\x221a"),
512 | ("Square", "\x25a1"),
513 | ("SquareIntersection", "\x2293"),
514 | ("SquareSubset", "\x228f"),
515 | ("SquareSubsetEqual", "\x2291"),
516 | ("SquareSuperset", "\x2290"),
517 | ("SquareSupersetEqual", "\x2292"),
518 | ("SquareUnion", "\x2294"),
519 | ("Sscr", "\x1d4ae"),
520 | ("Star", "\x22c6"),
521 | ("Sub", "\x22d0"),
522 | ("Subset", "\x22d0"),
523 | ("SubsetEqual", "\x2286"),
524 | ("Succeeds", "\x227b"),
525 | ("SucceedsEqual", "\x2ab0"),
526 | ("SucceedsSlantEqual", "\x227d"),
527 | ("SucceedsTilde", "\x227f"),
528 | ("SuchThat", "\x220b"),
529 | ("Sum", "\x2211"),
530 | ("Sup", "\x22d1"),
531 | ("Superset", "\x2283"),
532 | ("SupersetEqual", "\x2287"),
533 | ("Supset", "\x22d1"),
534 | ("THOR", "\x00de"),
535 | ("THORN", "\x00de"),
536 | ("TRADE", "\x2122"),
537 | ("TSHcy", "\x040b"),
538 | ("TScy", "\x0426"),
539 | ("Tab", "\x0009"),
540 | ("Tau", "\x03a4"),
541 | ("Tcaron", "\x0164"),
542 | ("Tcedil", "\x0162"),
543 | ("Tcy", "\x0422"),
544 | ("Tfr", "\x1d517"),
545 | ("Therefore", "\x2234"),
546 | ("Theta", "\x0398"),
547 | ("ThickSpace", "\x205f\x200a"),
548 | ("ThinSpace", "\x2009"),
549 | ("Tilde", "\x223c"),
550 | ("TildeEqual", "\x2243"),
551 | ("TildeFullEqual", "\x2245"),
552 | ("TildeTilde", "\x2248"),
553 | ("Topf", "\x1d54b"),
554 | ("TripleDot", "\x20db"),
555 | ("Tscr", "\x1d4af"),
556 | ("Tstrok", "\x0166"),
557 | ("Uacut", "\x00da"),
558 | ("Uacute", "\x00da"),
559 | ("Uarr", "\x219f"),
560 | ("Uarrocir", "\x2949"),
561 | ("Ubrcy", "\x040e"),
562 | ("Ubreve", "\x016c"),
563 | ("Ucir", "\x00db"),
564 | ("Ucirc", "\x00db"),
565 | ("Ucy", "\x0423"),
566 | ("Udblac", "\x0170"),
567 | ("Ufr", "\x1d518"),
568 | ("Ugrav", "\x00d9"),
569 | ("Ugrave", "\x00d9"),
570 | ("Umacr", "\x016a"),
571 | ("UnderBar", "\x005f"),
572 | ("UnderBrace", "\x23df"),
573 | ("UnderBracket", "\x23b5"),
574 | ("UnderParenthesis", "\x23dd"),
575 | ("Union", "\x22c3"),
576 | ("UnionPlus", "\x228e"),
577 | ("Uogon", "\x0172"),
578 | ("Uopf", "\x1d54c"),
579 | ("UpArrow", "\x2191"),
580 | ("UpArrowBar", "\x2912"),
581 | ("UpArrowDownArrow", "\x21c5"),
582 | ("UpDownArrow", "\x2195"),
583 | ("UpEquilibrium", "\x296e"),
584 | ("UpTee", "\x22a5"),
585 | ("UpTeeArrow", "\x21a5"),
586 | ("Uparrow", "\x21d1"),
587 | ("Updownarrow", "\x21d5"),
588 | ("UpperLeftArrow", "\x2196"),
589 | ("UpperRightArrow", "\x2197"),
590 | ("Upsi", "\x03d2"),
591 | ("Upsilon", "\x03a5"),
592 | ("Uring", "\x016e"),
593 | ("Uscr", "\x1d4b0"),
594 | ("Utilde", "\x0168"),
595 | ("Uum", "\x00dc"),
596 | ("Uuml", "\x00dc"),
597 | ("VDash", "\x22ab"),
598 | ("Vbar", "\x2aeb"),
599 | ("Vcy", "\x0412"),
600 | ("Vdash", "\x22a9"),
601 | ("Vdashl", "\x2ae6"),
602 | ("Vee", "\x22c1"),
603 | ("Verbar", "\x2016"),
604 | ("Vert", "\x2016"),
605 | ("VerticalBar", "\x2223"),
606 | ("VerticalLine", "\x007c"),
607 | ("VerticalSeparator", "\x2758"),
608 | ("VerticalTilde", "\x2240"),
609 | ("VeryThinSpace", "\x200a"),
610 | ("Vfr", "\x1d519"),
611 | ("Vopf", "\x1d54d"),
612 | ("Vscr", "\x1d4b1"),
613 | ("Vvdash", "\x22aa"),
614 | ("Wcirc", "\x0174"),
615 | ("Wedge", "\x22c0"),
616 | ("Wfr", "\x1d51a"),
617 | ("Wopf", "\x1d54e"),
618 | ("Wscr", "\x1d4b2"),
619 | ("Xfr", "\x1d51b"),
620 | ("Xi", "\x039e"),
621 | ("Xopf", "\x1d54f"),
622 | ("Xscr", "\x1d4b3"),
623 | ("YAcy", "\x042f"),
624 | ("YIcy", "\x0407"),
625 | ("YUcy", "\x042e"),
626 | ("Yacut", "\x00dd"),
627 | ("Yacute", "\x00dd"),
628 | ("Ycirc", "\x0176"),
629 | ("Ycy", "\x042b"),
630 | ("Yfr", "\x1d51c"),
631 | ("Yopf", "\x1d550"),
632 | ("Yscr", "\x1d4b4"),
633 | ("Yuml", "\x0178"),
634 | ("ZHcy", "\x0416"),
635 | ("Zacute", "\x0179"),
636 | ("Zcaron", "\x017d"),
637 | ("Zcy", "\x0417"),
638 | ("Zdot", "\x017b"),
639 | ("ZeroWidthSpace", "\x200b"),
640 | ("Zeta", "\x0396"),
641 | ("Zfr", "\x2128"),
642 | ("Zopf", "\x2124"),
643 | ("Zscr", "\x1d4b5"),
644 | ("aacut", "\x00e1"),
645 | ("aacute", "\x00e1"),
646 | ("abreve", "\x0103"),
647 | ("ac", "\x223e"),
648 | ("acE", "\x223e\x0333"),
649 | ("acd", "\x223f"),
650 | ("acir", "\x00e2"),
651 | ("acirc", "\x00e2"),
652 | ("acut", "\x00b4"),
653 | ("acute", "\x00b4"),
654 | ("acy", "\x0430"),
655 | ("aeli", "\x00e6"),
656 | ("aelig", "\x00e6"),
657 | ("af", "\x2061"),
658 | ("afr", "\x1d51e"),
659 | ("agrav", "\x00e0"),
660 | ("agrave", "\x00e0"),
661 | ("alefsym", "\x2135"),
662 | ("aleph", "\x2135"),
663 | ("alpha", "\x03b1"),
664 | ("amacr", "\x0101"),
665 | ("amalg", "\x2a3f"),
666 | ("am", "\x0026"),
667 | ("amp", "\x0026"),
668 | ("and", "\x2227"),
669 | ("andand", "\x2a55"),
670 | ("andd", "\x2a5c"),
671 | ("andslope", "\x2a58"),
672 | ("andv", "\x2a5a"),
673 | ("ang", "\x2220"),
674 | ("ange", "\x29a4"),
675 | ("angle", "\x2220"),
676 | ("angmsd", "\x2221"),
677 | ("angmsdaa", "\x29a8"),
678 | ("angmsdab", "\x29a9"),
679 | ("angmsdac", "\x29aa"),
680 | ("angmsdad", "\x29ab"),
681 | ("angmsdae", "\x29ac"),
682 | ("angmsdaf", "\x29ad"),
683 | ("angmsdag", "\x29ae"),
684 | ("angmsdah", "\x29af"),
685 | ("angrt", "\x221f"),
686 | ("angrtvb", "\x22be"),
687 | ("angrtvbd", "\x299d"),
688 | ("angsph", "\x2222"),
689 | ("angst", "\x00c5"),
690 | ("angzarr", "\x237c"),
691 | ("aogon", "\x0105"),
692 | ("aopf", "\x1d552"),
693 | ("ap", "\x2248"),
694 | ("apE", "\x2a70"),
695 | ("apacir", "\x2a6f"),
696 | ("ape", "\x224a"),
697 | ("apid", "\x224b"),
698 | ("apos", "\x0027"),
699 | ("approx", "\x2248"),
700 | ("approxeq", "\x224a"),
701 | ("arin", "\x00e5"),
702 | ("aring", "\x00e5"),
703 | ("ascr", "\x1d4b6"),
704 | ("ast", "\x002a"),
705 | ("asymp", "\x2248"),
706 | ("asympeq", "\x224d"),
707 | ("atild", "\x00e3"),
708 | ("atilde", "\x00e3"),
709 | ("aum", "\x00e4"),
710 | ("auml", "\x00e4"),
711 | ("awconint", "\x2233"),
712 | ("awint", "\x2a11"),
713 | ("bNot", "\x2aed"),
714 | ("backcong", "\x224c"),
715 | ("backepsilon", "\x03f6"),
716 | ("backprime", "\x2035"),
717 | ("backsim", "\x223d"),
718 | ("backsimeq", "\x22cd"),
719 | ("barvee", "\x22bd"),
720 | ("barwed", "\x2305"),
721 | ("barwedge", "\x2305"),
722 | ("bbrk", "\x23b5"),
723 | ("bbrktbrk", "\x23b6"),
724 | ("bcong", "\x224c"),
725 | ("bcy", "\x0431"),
726 | ("bdquo", "\x201e"),
727 | ("becaus", "\x2235"),
728 | ("because", "\x2235"),
729 | ("bemptyv", "\x29b0"),
730 | ("bepsi", "\x03f6"),
731 | ("bernou", "\x212c"),
732 | ("beta", "\x03b2"),
733 | ("beth", "\x2136"),
734 | ("between", "\x226c"),
735 | ("bfr", "\x1d51f"),
736 | ("bigcap", "\x22c2"),
737 | ("bigcirc", "\x25ef"),
738 | ("bigcup", "\x22c3"),
739 | ("bigodot", "\x2a00"),
740 | ("bigoplus", "\x2a01"),
741 | ("bigotimes", "\x2a02"),
742 | ("bigsqcup", "\x2a06"),
743 | ("bigstar", "\x2605"),
744 | ("bigtriangledown", "\x25bd"),
745 | ("bigtriangleup", "\x25b3"),
746 | ("biguplus", "\x2a04"),
747 | ("bigvee", "\x22c1"),
748 | ("bigwedge", "\x22c0"),
749 | ("bkarow", "\x290d"),
750 | ("blacklozenge", "\x29eb"),
751 | ("blacksquare", "\x25aa"),
752 | ("blacktriangle", "\x25b4"),
753 | ("blacktriangledown", "\x25be"),
754 | ("blacktriangleleft", "\x25c2"),
755 | ("blacktriangleright", "\x25b8"),
756 | ("blank", "\x2423"),
757 | ("blk12", "\x2592"),
758 | ("blk14", "\x2591"),
759 | ("blk34", "\x2593"),
760 | ("block", "\x2588"),
761 | ("bne", "\x003d\x20e5"),
762 | ("bnequiv", "\x2261\x20e5"),
763 | ("bnot", "\x2310"),
764 | ("bopf", "\x1d553"),
765 | ("bot", "\x22a5"),
766 | ("bottom", "\x22a5"),
767 | ("bowtie", "\x22c8"),
768 | ("boxDL", "\x2557"),
769 | ("boxDR", "\x2554"),
770 | ("boxDl", "\x2556"),
771 | ("boxDr", "\x2553"),
772 | ("boxH", "\x2550"),
773 | ("boxHD", "\x2566"),
774 | ("boxHU", "\x2569"),
775 | ("boxHd", "\x2564"),
776 | ("boxHu", "\x2567"),
777 | ("boxUL", "\x255d"),
778 | ("boxUR", "\x255a"),
779 | ("boxUl", "\x255c"),
780 | ("boxUr", "\x2559"),
781 | ("boxV", "\x2551"),
782 | ("boxVH", "\x256c"),
783 | ("boxVL", "\x2563"),
784 | ("boxVR", "\x2560"),
785 | ("boxVh", "\x256b"),
786 | ("boxVl", "\x2562"),
787 | ("boxVr", "\x255f"),
788 | ("boxbox", "\x29c9"),
789 | ("boxdL", "\x2555"),
790 | ("boxdR", "\x2552"),
791 | ("boxdl", "\x2510"),
792 | ("boxdr", "\x250c"),
793 | ("boxh", "\x2500"),
794 | ("boxhD", "\x2565"),
795 | ("boxhU", "\x2568"),
796 | ("boxhd", "\x252c"),
797 | ("boxhu", "\x2534"),
798 | ("boxminus", "\x229f"),
799 | ("boxplus", "\x229e"),
800 | ("boxtimes", "\x22a0"),
801 | ("boxuL", "\x255b"),
802 | ("boxuR", "\x2558"),
803 | ("boxul", "\x2518"),
804 | ("boxur", "\x2514"),
805 | ("boxv", "\x2502"),
806 | ("boxvH", "\x256a"),
807 | ("boxvL", "\x2561"),
808 | ("boxvR", "\x255e"),
809 | ("boxvh", "\x253c"),
810 | ("boxvl", "\x2524"),
811 | ("boxvr", "\x251c"),
812 | ("bprime", "\x2035"),
813 | ("breve", "\x02d8"),
814 | ("brvba", "\x00a6"),
815 | ("brvbar", "\x00a6"),
816 | ("bscr", "\x1d4b7"),
817 | ("bsemi", "\x204f"),
818 | ("bsim", "\x223d"),
819 | ("bsime", "\x22cd"),
820 | ("bsol", "\x005c"),
821 | ("bsolb", "\x29c5"),
822 | ("bsolhsub", "\x27c8"),
823 | ("bull", "\x2022"),
824 | ("bullet", "\x2022"),
825 | ("bump", "\x224e"),
826 | ("bumpE", "\x2aae"),
827 | ("bumpe", "\x224f"),
828 | ("bumpeq", "\x224f"),
829 | ("cacute", "\x0107"),
830 | ("cap", "\x2229"),
831 | ("capand", "\x2a44"),
832 | ("capbrcup", "\x2a49"),
833 | ("capcap", "\x2a4b"),
834 | ("capcup", "\x2a47"),
835 | ("capdot", "\x2a40"),
836 | ("caps", "\x2229\xfe00"),
837 | ("caret", "\x2041"),
838 | ("caron", "\x02c7"),
839 | ("ccaps", "\x2a4d"),
840 | ("ccaron", "\x010d"),
841 | ("ccedi", "\x00e7"),
842 | ("ccedil", "\x00e7"),
843 | ("ccirc", "\x0109"),
844 | ("ccups", "\x2a4c"),
845 | ("ccupssm", "\x2a50"),
846 | ("cdot", "\x010b"),
847 | ("cedi", "\x00b8"),
848 | ("cedil", "\x00b8"),
849 | ("cemptyv", "\x29b2"),
850 | ("cen", "\x00a2"),
851 | ("cent", "\x00a2"),
852 | ("centerdot", "\x00b7"),
853 | ("cfr", "\x1d520"),
854 | ("chcy", "\x0447"),
855 | ("check", "\x2713"),
856 | ("checkmark", "\x2713"),
857 | ("chi", "\x03c7"),
858 | ("cir", "\x25cb"),
859 | ("cirE", "\x29c3"),
860 | ("circ", "\x02c6"),
861 | ("circeq", "\x2257"),
862 | ("circlearrowleft", "\x21ba"),
863 | ("circlearrowright", "\x21bb"),
864 | ("circledR", "\x00ae"),
865 | ("circledS", "\x24c8"),
866 | ("circledast", "\x229b"),
867 | ("circledcirc", "\x229a"),
868 | ("circleddash", "\x229d"),
869 | ("cire", "\x2257"),
870 | ("cirfnint", "\x2a10"),
871 | ("cirmid", "\x2aef"),
872 | ("cirscir", "\x29c2"),
873 | ("clubs", "\x2663"),
874 | ("clubsuit", "\x2663"),
875 | ("colon", "\x003a"),
876 | ("colone", "\x2254"),
877 | ("coloneq", "\x2254"),
878 | ("comma", "\x002c"),
879 | ("commat", "\x0040"),
880 | ("comp", "\x2201"),
881 | ("compfn", "\x2218"),
882 | ("complement", "\x2201"),
883 | ("complexes", "\x2102"),
884 | ("cong", "\x2245"),
885 | ("congdot", "\x2a6d"),
886 | ("conint", "\x222e"),
887 | ("copf", "\x1d554"),
888 | ("coprod", "\x2210"),
889 | ("cop", "\x00a9"),
890 | ("copy", "\x00a9"),
891 | ("copysr", "\x2117"),
892 | ("crarr", "\x21b5"),
893 | ("cross", "\x2717"),
894 | ("cscr", "\x1d4b8"),
895 | ("csub", "\x2acf"),
896 | ("csube", "\x2ad1"),
897 | ("csup", "\x2ad0"),
898 | ("csupe", "\x2ad2"),
899 | ("ctdot", "\x22ef"),
900 | ("cudarrl", "\x2938"),
901 | ("cudarrr", "\x2935"),
902 | ("cuepr", "\x22de"),
903 | ("cuesc", "\x22df"),
904 | ("cularr", "\x21b6"),
905 | ("cularrp", "\x293d"),
906 | ("cup", "\x222a"),
907 | ("cupbrcap", "\x2a48"),
908 | ("cupcap", "\x2a46"),
909 | ("cupcup", "\x2a4a"),
910 | ("cupdot", "\x228d"),
911 | ("cupor", "\x2a45"),
912 | ("cups", "\x222a\xfe00"),
913 | ("curarr", "\x21b7"),
914 | ("curarrm", "\x293c"),
915 | ("curlyeqprec", "\x22de"),
916 | ("curlyeqsucc", "\x22df"),
917 | ("curlyvee", "\x22ce"),
918 | ("curlywedge", "\x22cf"),
919 | ("curre", "\x00a4"),
920 | ("curren", "\x00a4"),
921 | ("curvearrowleft", "\x21b6"),
922 | ("curvearrowright", "\x21b7"),
923 | ("cuvee", "\x22ce"),
924 | ("cuwed", "\x22cf"),
925 | ("cwconint", "\x2232"),
926 | ("cwint", "\x2231"),
927 | ("cylcty", "\x232d"),
928 | ("dArr", "\x21d3"),
929 | ("dHar", "\x2965"),
930 | ("dagger", "\x2020"),
931 | ("daleth", "\x2138"),
932 | ("darr", "\x2193"),
933 | ("dash", "\x2010"),
934 | ("dashv", "\x22a3"),
935 | ("dbkarow", "\x290f"),
936 | ("dblac", "\x02dd"),
937 | ("dcaron", "\x010f"),
938 | ("dcy", "\x0434"),
939 | ("dd", "\x2146"),
940 | ("ddagger", "\x2021"),
941 | ("ddarr", "\x21ca"),
942 | ("ddotseq", "\x2a77"),
943 | ("de", "\x00b0"),
944 | ("deg", "\x00b0"),
945 | ("delta", "\x03b4"),
946 | ("demptyv", "\x29b1"),
947 | ("dfisht", "\x297f"),
948 | ("dfr", "\x1d521"),
949 | ("dharl", "\x21c3"),
950 | ("dharr", "\x21c2"),
951 | ("diam", "\x22c4"),
952 | ("diamond", "\x22c4"),
953 | ("diamondsuit", "\x2666"),
954 | ("diams", "\x2666"),
955 | ("die", "\x00a8"),
956 | ("digamma", "\x03dd"),
957 | ("disin", "\x22f2"),
958 | ("div", "\x00f7"),
959 | ("divid", "\x00f7"),
960 | ("divide", "\x00f7"),
961 | ("divideontimes", "\x22c7"),
962 | ("divonx", "\x22c7"),
963 | ("djcy", "\x0452"),
964 | ("dlcorn", "\x231e"),
965 | ("dlcrop", "\x230d"),
966 | ("dollar", "\x0024"),
967 | ("dopf", "\x1d555"),
968 | ("dot", "\x02d9"),
969 | ("doteq", "\x2250"),
970 | ("doteqdot", "\x2251"),
971 | ("dotminus", "\x2238"),
972 | ("dotplus", "\x2214"),
973 | ("dotsquare", "\x22a1"),
974 | ("doublebarwedge", "\x2306"),
975 | ("downarrow", "\x2193"),
976 | ("downdownarrows", "\x21ca"),
977 | ("downharpoonleft", "\x21c3"),
978 | ("downharpoonright", "\x21c2"),
979 | ("drbkarow", "\x2910"),
980 | ("drcorn", "\x231f"),
981 | ("drcrop", "\x230c"),
982 | ("dscr", "\x1d4b9"),
983 | ("dscy", "\x0455"),
984 | ("dsol", "\x29f6"),
985 | ("dstrok", "\x0111"),
986 | ("dtdot", "\x22f1"),
987 | ("dtri", "\x25bf"),
988 | ("dtrif", "\x25be"),
989 | ("duarr", "\x21f5"),
990 | ("duhar", "\x296f"),
991 | ("dwangle", "\x29a6"),
992 | ("dzcy", "\x045f"),
993 | ("dzigrarr", "\x27ff"),
994 | ("eDDot", "\x2a77"),
995 | ("eDot", "\x2251"),
996 | ("eacut", "\x00e9"),
997 | ("eacute", "\x00e9"),
998 | ("easter", "\x2a6e"),
999 | ("ecaron", "\x011b"),
1000 | ("ecir", "\x2256"),
1001 | ("ecir", "\x00ea"),
1002 | ("ecirc", "\x00ea"),
1003 | ("ecolon", "\x2255"),
1004 | ("ecy", "\x044d"),
1005 | ("edot", "\x0117"),
1006 | ("ee", "\x2147"),
1007 | ("efDot", "\x2252"),
1008 | ("efr", "\x1d522"),
1009 | ("eg", "\x2a9a"),
1010 | ("egrav", "\x00e8"),
1011 | ("egrave", "\x00e8"),
1012 | ("egs", "\x2a96"),
1013 | ("egsdot", "\x2a98"),
1014 | ("el", "\x2a99"),
1015 | ("elinters", "\x23e7"),
1016 | ("ell", "\x2113"),
1017 | ("els", "\x2a95"),
1018 | ("elsdot", "\x2a97"),
1019 | ("emacr", "\x0113"),
1020 | ("empty", "\x2205"),
1021 | ("emptyset", "\x2205"),
1022 | ("emptyv", "\x2205"),
1023 | ("emsp13", "\x2004"),
1024 | ("emsp14", "\x2005"),
1025 | ("emsp", "\x2003"),
1026 | ("eng", "\x014b"),
1027 | ("ensp", "\x2002"),
1028 | ("eogon", "\x0119"),
1029 | ("eopf", "\x1d556"),
1030 | ("epar", "\x22d5"),
1031 | ("eparsl", "\x29e3"),
1032 | ("eplus", "\x2a71"),
1033 | ("epsi", "\x03b5"),
1034 | ("epsilon", "\x03b5"),
1035 | ("epsiv", "\x03f5"),
1036 | ("eqcirc", "\x2256"),
1037 | ("eqcolon", "\x2255"),
1038 | ("eqsim", "\x2242"),
1039 | ("eqslantgtr", "\x2a96"),
1040 | ("eqslantless", "\x2a95"),
1041 | ("equals", "\x003d"),
1042 | ("equest", "\x225f"),
1043 | ("equiv", "\x2261"),
1044 | ("equivDD", "\x2a78"),
1045 | ("eqvparsl", "\x29e5"),
1046 | ("erDot", "\x2253"),
1047 | ("erarr", "\x2971"),
1048 | ("escr", "\x212f"),
1049 | ("esdot", "\x2250"),
1050 | ("esim", "\x2242"),
1051 | ("eta", "\x03b7"),
1052 | ("et", "\x00f0"),
1053 | ("eth", "\x00f0"),
1054 | ("eum", "\x00eb"),
1055 | ("euml", "\x00eb"),
1056 | ("euro", "\x20ac"),
1057 | ("excl", "\x0021"),
1058 | ("exist", "\x2203"),
1059 | ("expectation", "\x2130"),
1060 | ("exponentiale", "\x2147"),
1061 | ("fallingdotseq", "\x2252"),
1062 | ("fcy", "\x0444"),
1063 | ("female", "\x2640"),
1064 | ("ffilig", "\xfb03"),
1065 | ("fflig", "\xfb00"),
1066 | ("ffllig", "\xfb04"),
1067 | ("ffr", "\x1d523"),
1068 | ("filig", "\xfb01"),
1069 | ("fjlig", "\x0066\x006a"),
1070 | ("flat", "\x266d"),
1071 | ("fllig", "\xfb02"),
1072 | ("fltns", "\x25b1"),
1073 | ("fnof", "\x0192"),
1074 | ("fopf", "\x1d557"),
1075 | ("forall", "\x2200"),
1076 | ("fork", "\x22d4"),
1077 | ("forkv", "\x2ad9"),
1078 | ("fpartint", "\x2a0d"),
1079 | ("frac1", "\x00bd"),
1080 | ("frac12", "\x00bd"),
1081 | ("frac13", "\x2153"),
1082 | ("frac1", "\x00bc"),
1083 | ("frac14", "\x00bc"),
1084 | ("frac15", "\x2155"),
1085 | ("frac16", "\x2159"),
1086 | ("frac18", "\x215b"),
1087 | ("frac23", "\x2154"),
1088 | ("frac25", "\x2156"),
1089 | ("frac3", "\x00be"),
1090 | ("frac34", "\x00be"),
1091 | ("frac35", "\x2157"),
1092 | ("frac38", "\x215c"),
1093 | ("frac45", "\x2158"),
1094 | ("frac56", "\x215a"),
1095 | ("frac58", "\x215d"),
1096 | ("frac78", "\x215e"),
1097 | ("frasl", "\x2044"),
1098 | ("frown", "\x2322"),
1099 | ("fscr", "\x1d4bb"),
1100 | ("gE", "\x2267"),
1101 | ("gEl", "\x2a8c"),
1102 | ("gacute", "\x01f5"),
1103 | ("gamma", "\x03b3"),
1104 | ("gammad", "\x03dd"),
1105 | ("gap", "\x2a86"),
1106 | ("gbreve", "\x011f"),
1107 | ("gcirc", "\x011d"),
1108 | ("gcy", "\x0433"),
1109 | ("gdot", "\x0121"),
1110 | ("ge", "\x2265"),
1111 | ("gel", "\x22db"),
1112 | ("geq", "\x2265"),
1113 | ("geqq", "\x2267"),
1114 | ("geqslant", "\x2a7e"),
1115 | ("ges", "\x2a7e"),
1116 | ("gescc", "\x2aa9"),
1117 | ("gesdot", "\x2a80"),
1118 | ("gesdoto", "\x2a82"),
1119 | ("gesdotol", "\x2a84"),
1120 | ("gesl", "\x22db\xfe00"),
1121 | ("gesles", "\x2a94"),
1122 | ("gfr", "\x1d524"),
1123 | ("gg", "\x226b"),
1124 | ("ggg", "\x22d9"),
1125 | ("gimel", "\x2137"),
1126 | ("gjcy", "\x0453"),
1127 | ("gl", "\x2277"),
1128 | ("glE", "\x2a92"),
1129 | ("gla", "\x2aa5"),
1130 | ("glj", "\x2aa4"),
1131 | ("gnE", "\x2269"),
1132 | ("gnap", "\x2a8a"),
1133 | ("gnapprox", "\x2a8a"),
1134 | ("gne", "\x2a88"),
1135 | ("gneq", "\x2a88"),
1136 | ("gneqq", "\x2269"),
1137 | ("gnsim", "\x22e7"),
1138 | ("gopf", "\x1d558"),
1139 | ("grave", "\x0060"),
1140 | ("gscr", "\x210a"),
1141 | ("gsim", "\x2273"),
1142 | ("gsime", "\x2a8e"),
1143 | ("gsiml", "\x2a90"),
1144 | ("g", "\x003e"),
1145 | ("gt", "\x003e"),
1146 | ("gtcc", "\x2aa7"),
1147 | ("gtcir", "\x2a7a"),
1148 | ("gtdot", "\x22d7"),
1149 | ("gtlPar", "\x2995"),
1150 | ("gtquest", "\x2a7c"),
1151 | ("gtrapprox", "\x2a86"),
1152 | ("gtrarr", "\x2978"),
1153 | ("gtrdot", "\x22d7"),
1154 | ("gtreqless", "\x22db"),
1155 | ("gtreqqless", "\x2a8c"),
1156 | ("gtrless", "\x2277"),
1157 | ("gtrsim", "\x2273"),
1158 | ("gvertneqq", "\x2269\xfe00"),
1159 | ("gvnE", "\x2269\xfe00"),
1160 | ("hArr", "\x21d4"),
1161 | ("hairsp", "\x200a"),
1162 | ("half", "\x00bd"),
1163 | ("hamilt", "\x210b"),
1164 | ("hardcy", "\x044a"),
1165 | ("harr", "\x2194"),
1166 | ("harrcir", "\x2948"),
1167 | ("harrw", "\x21ad"),
1168 | ("hbar", "\x210f"),
1169 | ("hcirc", "\x0125"),
1170 | ("hearts", "\x2665"),
1171 | ("heartsuit", "\x2665"),
1172 | ("hellip", "\x2026"),
1173 | ("hercon", "\x22b9"),
1174 | ("hfr", "\x1d525"),
1175 | ("hksearow", "\x2925"),
1176 | ("hkswarow", "\x2926"),
1177 | ("hoarr", "\x21ff"),
1178 | ("homtht", "\x223b"),
1179 | ("hookleftarrow", "\x21a9"),
1180 | ("hookrightarrow", "\x21aa"),
1181 | ("hopf", "\x1d559"),
1182 | ("horbar", "\x2015"),
1183 | ("hscr", "\x1d4bd"),
1184 | ("hslash", "\x210f"),
1185 | ("hstrok", "\x0127"),
1186 | ("hybull", "\x2043"),
1187 | ("hyphen", "\x2010"),
1188 | ("iacut", "\x00ed"),
1189 | ("iacute", "\x00ed"),
1190 | ("ic", "\x2063"),
1191 | ("icir", "\x00ee"),
1192 | ("icirc", "\x00ee"),
1193 | ("icy", "\x0438"),
1194 | ("iecy", "\x0435"),
1195 | ("iexc", "\x00a1"),
1196 | ("iexcl", "\x00a1"),
1197 | ("iff", "\x21d4"),
1198 | ("ifr", "\x1d526"),
1199 | ("igrav", "\x00ec"),
1200 | ("igrave", "\x00ec"),
1201 | ("ii", "\x2148"),
1202 | ("iiiint", "\x2a0c"),
1203 | ("iiint", "\x222d"),
1204 | ("iinfin", "\x29dc"),
1205 | ("iiota", "\x2129"),
1206 | ("ijlig", "\x0133"),
1207 | ("imacr", "\x012b"),
1208 | ("image", "\x2111"),
1209 | ("imagline", "\x2110"),
1210 | ("imagpart", "\x2111"),
1211 | ("imath", "\x0131"),
1212 | ("imof", "\x22b7"),
1213 | ("imped", "\x01b5"),
1214 | ("in", "\x2208"),
1215 | ("incare", "\x2105"),
1216 | ("infin", "\x221e"),
1217 | ("infintie", "\x29dd"),
1218 | ("inodot", "\x0131"),
1219 | ("int", "\x222b"),
1220 | ("intcal", "\x22ba"),
1221 | ("integers", "\x2124"),
1222 | ("intercal", "\x22ba"),
1223 | ("intlarhk", "\x2a17"),
1224 | ("intprod", "\x2a3c"),
1225 | ("iocy", "\x0451"),
1226 | ("iogon", "\x012f"),
1227 | ("iopf", "\x1d55a"),
1228 | ("iota", "\x03b9"),
1229 | ("iprod", "\x2a3c"),
1230 | ("iques", "\x00bf"),
1231 | ("iquest", "\x00bf"),
1232 | ("iscr", "\x1d4be"),
1233 | ("isin", "\x2208"),
1234 | ("isinE", "\x22f9"),
1235 | ("isindot", "\x22f5"),
1236 | ("isins", "\x22f4"),
1237 | ("isinsv", "\x22f3"),
1238 | ("isinv", "\x2208"),
1239 | ("it", "\x2062"),
1240 | ("itilde", "\x0129"),
1241 | ("iukcy", "\x0456"),
1242 | ("ium", "\x00ef"),
1243 | ("iuml", "\x00ef"),
1244 | ("jcirc", "\x0135"),
1245 | ("jcy", "\x0439"),
1246 | ("jfr", "\x1d527"),
1247 | ("jmath", "\x0237"),
1248 | ("jopf", "\x1d55b"),
1249 | ("jscr", "\x1d4bf"),
1250 | ("jsercy", "\x0458"),
1251 | ("jukcy", "\x0454"),
1252 | ("kappa", "\x03ba"),
1253 | ("kappav", "\x03f0"),
1254 | ("kcedil", "\x0137"),
1255 | ("kcy", "\x043a"),
1256 | ("kfr", "\x1d528"),
1257 | ("kgreen", "\x0138"),
1258 | ("khcy", "\x0445"),
1259 | ("kjcy", "\x045c"),
1260 | ("kopf", "\x1d55c"),
1261 | ("kscr", "\x1d4c0"),
1262 | ("lAarr", "\x21da"),
1263 | ("lArr", "\x21d0"),
1264 | ("lAtail", "\x291b"),
1265 | ("lBarr", "\x290e"),
1266 | ("lE", "\x2266"),
1267 | ("lEg", "\x2a8b"),
1268 | ("lHar", "\x2962"),
1269 | ("lacute", "\x013a"),
1270 | ("laemptyv", "\x29b4"),
1271 | ("lagran", "\x2112"),
1272 | ("lambda", "\x03bb"),
1273 | ("lang", "\x27e8"),
1274 | ("langd", "\x2991"),
1275 | ("langle", "\x27e8"),
1276 | ("lap", "\x2a85"),
1277 | ("laqu", "\x00ab"),
1278 | ("laquo", "\x00ab"),
1279 | ("larr", "\x2190"),
1280 | ("larrb", "\x21e4"),
1281 | ("larrbfs", "\x291f"),
1282 | ("larrfs", "\x291d"),
1283 | ("larrhk", "\x21a9"),
1284 | ("larrlp", "\x21ab"),
1285 | ("larrpl", "\x2939"),
1286 | ("larrsim", "\x2973"),
1287 | ("larrtl", "\x21a2"),
1288 | ("lat", "\x2aab"),
1289 | ("latail", "\x2919"),
1290 | ("late", "\x2aad"),
1291 | ("lates", "\x2aad\xfe00"),
1292 | ("lbarr", "\x290c"),
1293 | ("lbbrk", "\x2772"),
1294 | ("lbrace", "\x007b"),
1295 | ("lbrack", "\x005b"),
1296 | ("lbrke", "\x298b"),
1297 | ("lbrksld", "\x298f"),
1298 | ("lbrkslu", "\x298d"),
1299 | ("lcaron", "\x013e"),
1300 | ("lcedil", "\x013c"),
1301 | ("lceil", "\x2308"),
1302 | ("lcub", "\x007b"),
1303 | ("lcy", "\x043b"),
1304 | ("ldca", "\x2936"),
1305 | ("ldquo", "\x201c"),
1306 | ("ldquor", "\x201e"),
1307 | ("ldrdhar", "\x2967"),
1308 | ("ldrushar", "\x294b"),
1309 | ("ldsh", "\x21b2"),
1310 | ("le", "\x2264"),
1311 | ("leftarrow", "\x2190"),
1312 | ("leftarrowtail", "\x21a2"),
1313 | ("leftharpoondown", "\x21bd"),
1314 | ("leftharpoonup", "\x21bc"),
1315 | ("leftleftarrows", "\x21c7"),
1316 | ("leftrightarrow", "\x2194"),
1317 | ("leftrightarrows", "\x21c6"),
1318 | ("leftrightharpoons", "\x21cb"),
1319 | ("leftrightsquigarrow", "\x21ad"),
1320 | ("leftthreetimes", "\x22cb"),
1321 | ("leg", "\x22da"),
1322 | ("leq", "\x2264"),
1323 | ("leqq", "\x2266"),
1324 | ("leqslant", "\x2a7d"),
1325 | ("les", "\x2a7d"),
1326 | ("lescc", "\x2aa8"),
1327 | ("lesdot", "\x2a7f"),
1328 | ("lesdoto", "\x2a81"),
1329 | ("lesdotor", "\x2a83"),
1330 | ("lesg", "\x22da\xfe00"),
1331 | ("lesges", "\x2a93"),
1332 | ("lessapprox", "\x2a85"),
1333 | ("lessdot", "\x22d6"),
1334 | ("lesseqgtr", "\x22da"),
1335 | ("lesseqqgtr", "\x2a8b"),
1336 | ("lessgtr", "\x2276"),
1337 | ("lesssim", "\x2272"),
1338 | ("lfisht", "\x297c"),
1339 | ("lfloor", "\x230a"),
1340 | ("lfr", "\x1d529"),
1341 | ("lg", "\x2276"),
1342 | ("lgE", "\x2a91"),
1343 | ("lhard", "\x21bd"),
1344 | ("lharu", "\x21bc"),
1345 | ("lharul", "\x296a"),
1346 | ("lhblk", "\x2584"),
1347 | ("ljcy", "\x0459"),
1348 | ("ll", "\x226a"),
1349 | ("llarr", "\x21c7"),
1350 | ("llcorner", "\x231e"),
1351 | ("llhard", "\x296b"),
1352 | ("lltri", "\x25fa"),
1353 | ("lmidot", "\x0140"),
1354 | ("lmoust", "\x23b0"),
1355 | ("lmoustache", "\x23b0"),
1356 | ("lnE", "\x2268"),
1357 | ("lnap", "\x2a89"),
1358 | ("lnapprox", "\x2a89"),
1359 | ("lne", "\x2a87"),
1360 | ("lneq", "\x2a87"),
1361 | ("lneqq", "\x2268"),
1362 | ("lnsim", "\x22e6"),
1363 | ("loang", "\x27ec"),
1364 | ("loarr", "\x21fd"),
1365 | ("lobrk", "\x27e6"),
1366 | ("longleftarrow", "\x27f5"),
1367 | ("longleftrightarrow", "\x27f7"),
1368 | ("longmapsto", "\x27fc"),
1369 | ("longrightarrow", "\x27f6"),
1370 | ("looparrowleft", "\x21ab"),
1371 | ("looparrowright", "\x21ac"),
1372 | ("lopar", "\x2985"),
1373 | ("lopf", "\x1d55d"),
1374 | ("loplus", "\x2a2d"),
1375 | ("lotimes", "\x2a34"),
1376 | ("lowast", "\x2217"),
1377 | ("lowbar", "\x005f"),
1378 | ("loz", "\x25ca"),
1379 | ("lozenge", "\x25ca"),
1380 | ("lozf", "\x29eb"),
1381 | ("lpar", "\x0028"),
1382 | ("lparlt", "\x2993"),
1383 | ("lrarr", "\x21c6"),
1384 | ("lrcorner", "\x231f"),
1385 | ("lrhar", "\x21cb"),
1386 | ("lrhard", "\x296d"),
1387 | ("lrm", "\x200e"),
1388 | ("lrtri", "\x22bf"),
1389 | ("lsaquo", "\x2039"),
1390 | ("lscr", "\x1d4c1"),
1391 | ("lsh", "\x21b0"),
1392 | ("lsim", "\x2272"),
1393 | ("lsime", "\x2a8d"),
1394 | ("lsimg", "\x2a8f"),
1395 | ("lsqb", "\x005b"),
1396 | ("lsquo", "\x2018"),
1397 | ("lsquor", "\x201a"),
1398 | ("lstrok", "\x0142"),
1399 | ("l", "\x003c"),
1400 | ("lt", "\x003c"),
1401 | ("ltcc", "\x2aa6"),
1402 | ("ltcir", "\x2a79"),
1403 | ("ltdot", "\x22d6"),
1404 | ("lthree", "\x22cb"),
1405 | ("ltimes", "\x22c9"),
1406 | ("ltlarr", "\x2976"),
1407 | ("ltquest", "\x2a7b"),
1408 | ("ltrPar", "\x2996"),
1409 | ("ltri", "\x25c3"),
1410 | ("ltrie", "\x22b4"),
1411 | ("ltrif", "\x25c2"),
1412 | ("lurdshar", "\x294a"),
1413 | ("luruhar", "\x2966"),
1414 | ("lvertneqq", "\x2268\xfe00"),
1415 | ("lvnE", "\x2268\xfe00"),
1416 | ("mDDot", "\x223a"),
1417 | ("mac", "\x00af"),
1418 | ("macr", "\x00af"),
1419 | ("male", "\x2642"),
1420 | ("malt", "\x2720"),
1421 | ("maltese", "\x2720"),
1422 | ("map", "\x21a6"),
1423 | ("mapsto", "\x21a6"),
1424 | ("mapstodown", "\x21a7"),
1425 | ("mapstoleft", "\x21a4"),
1426 | ("mapstoup", "\x21a5"),
1427 | ("marker", "\x25ae"),
1428 | ("mcomma", "\x2a29"),
1429 | ("mcy", "\x043c"),
1430 | ("mdash", "\x2014"),
1431 | ("measuredangle", "\x2221"),
1432 | ("mfr", "\x1d52a"),
1433 | ("mho", "\x2127"),
1434 | ("micr", "\x00b5"),
1435 | ("micro", "\x00b5"),
1436 | ("mid", "\x2223"),
1437 | ("midast", "\x002a"),
1438 | ("midcir", "\x2af0"),
1439 | ("middo", "\x00b7"),
1440 | ("middot", "\x00b7"),
1441 | ("minus", "\x2212"),
1442 | ("minusb", "\x229f"),
1443 | ("minusd", "\x2238"),
1444 | ("minusdu", "\x2a2a"),
1445 | ("mlcp", "\x2adb"),
1446 | ("mldr", "\x2026"),
1447 | ("mnplus", "\x2213"),
1448 | ("models", "\x22a7"),
1449 | ("mopf", "\x1d55e"),
1450 | ("mp", "\x2213"),
1451 | ("mscr", "\x1d4c2"),
1452 | ("mstpos", "\x223e"),
1453 | ("mu", "\x03bc"),
1454 | ("multimap", "\x22b8"),
1455 | ("mumap", "\x22b8"),
1456 | ("nGg", "\x22d9\x0338"),
1457 | ("nGt", "\x226b\x20d2"),
1458 | ("nGtv", "\x226b\x0338"),
1459 | ("nLeftarrow", "\x21cd"),
1460 | ("nLeftrightarrow", "\x21ce"),
1461 | ("nLl", "\x22d8\x0338"),
1462 | ("nLt", "\x226a\x20d2"),
1463 | ("nLtv", "\x226a\x0338"),
1464 | ("nRightarrow", "\x21cf"),
1465 | ("nVDash", "\x22af"),
1466 | ("nVdash", "\x22ae"),
1467 | ("nabla", "\x2207"),
1468 | ("nacute", "\x0144"),
1469 | ("nang", "\x2220\x20d2"),
1470 | ("nap", "\x2249"),
1471 | ("napE", "\x2a70\x0338"),
1472 | ("napid", "\x224b\x0338"),
1473 | ("napos", "\x0149"),
1474 | ("napprox", "\x2249"),
1475 | ("natur", "\x266e"),
1476 | ("natural", "\x266e"),
1477 | ("naturals", "\x2115"),
1478 | ("nbs", "\x00a0"),
1479 | ("nbsp", "\x00a0"),
1480 | ("nbump", "\x224e\x0338"),
1481 | ("nbumpe", "\x224f\x0338"),
1482 | ("ncap", "\x2a43"),
1483 | ("ncaron", "\x0148"),
1484 | ("ncedil", "\x0146"),
1485 | ("ncong", "\x2247"),
1486 | ("ncongdot", "\x2a6d\x0338"),
1487 | ("ncup", "\x2a42"),
1488 | ("ncy", "\x043d"),
1489 | ("ndash", "\x2013"),
1490 | ("ne", "\x2260"),
1491 | ("neArr", "\x21d7"),
1492 | ("nearhk", "\x2924"),
1493 | ("nearr", "\x2197"),
1494 | ("nearrow", "\x2197"),
1495 | ("nedot", "\x2250\x0338"),
1496 | ("nequiv", "\x2262"),
1497 | ("nesear", "\x2928"),
1498 | ("nesim", "\x2242\x0338"),
1499 | ("nexist", "\x2204"),
1500 | ("nexists", "\x2204"),
1501 | ("nfr", "\x1d52b"),
1502 | ("ngE", "\x2267\x0338"),
1503 | ("nge", "\x2271"),
1504 | ("ngeq", "\x2271"),
1505 | ("ngeqq", "\x2267\x0338"),
1506 | ("ngeqslant", "\x2a7e\x0338"),
1507 | ("nges", "\x2a7e\x0338"),
1508 | ("ngsim", "\x2275"),
1509 | ("ngt", "\x226f"),
1510 | ("ngtr", "\x226f"),
1511 | ("nhArr", "\x21ce"),
1512 | ("nharr", "\x21ae"),
1513 | ("nhpar", "\x2af2"),
1514 | ("ni", "\x220b"),
1515 | ("nis", "\x22fc"),
1516 | ("nisd", "\x22fa"),
1517 | ("niv", "\x220b"),
1518 | ("njcy", "\x045a"),
1519 | ("nlArr", "\x21cd"),
1520 | ("nlE", "\x2266\x0338"),
1521 | ("nlarr", "\x219a"),
1522 | ("nldr", "\x2025"),
1523 | ("nle", "\x2270"),
1524 | ("nleftarrow", "\x219a"),
1525 | ("nleftrightarrow", "\x21ae"),
1526 | ("nleq", "\x2270"),
1527 | ("nleqq", "\x2266\x0338"),
1528 | ("nleqslant", "\x2a7d\x0338"),
1529 | ("nles", "\x2a7d\x0338"),
1530 | ("nless", "\x226e"),
1531 | ("nlsim", "\x2274"),
1532 | ("nlt", "\x226e"),
1533 | ("nltri", "\x22ea"),
1534 | ("nltrie", "\x22ec"),
1535 | ("nmid", "\x2224"),
1536 | ("nopf", "\x1d55f"),
1537 | ("no", "\x00ac"),
1538 | ("not", "\x00ac"),
1539 | ("notin", "\x2209"),
1540 | ("notinE", "\x22f9\x0338"),
1541 | ("notindot", "\x22f5\x0338"),
1542 | ("notinva", "\x2209"),
1543 | ("notinvb", "\x22f7"),
1544 | ("notinvc", "\x22f6"),
1545 | ("notni", "\x220c"),
1546 | ("notniva", "\x220c"),
1547 | ("notnivb", "\x22fe"),
1548 | ("notnivc", "\x22fd"),
1549 | ("npar", "\x2226"),
1550 | ("nparallel", "\x2226"),
1551 | ("nparsl", "\x2afd\x20e5"),
1552 | ("npart", "\x2202\x0338"),
1553 | ("npolint", "\x2a14"),
1554 | ("npr", "\x2280"),
1555 | ("nprcue", "\x22e0"),
1556 | ("npre", "\x2aaf\x0338"),
1557 | ("nprec", "\x2280"),
1558 | ("npreceq", "\x2aaf\x0338"),
1559 | ("nrArr", "\x21cf"),
1560 | ("nrarr", "\x219b"),
1561 | ("nrarrc", "\x2933\x0338"),
1562 | ("nrarrw", "\x219d\x0338"),
1563 | ("nrightarrow", "\x219b"),
1564 | ("nrtri", "\x22eb"),
1565 | ("nrtrie", "\x22ed"),
1566 | ("nsc", "\x2281"),
1567 | ("nsccue", "\x22e1"),
1568 | ("nsce", "\x2ab0\x0338"),
1569 | ("nscr", "\x1d4c3"),
1570 | ("nshortmid", "\x2224"),
1571 | ("nshortparallel", "\x2226"),
1572 | ("nsim", "\x2241"),
1573 | ("nsime", "\x2244"),
1574 | ("nsimeq", "\x2244"),
1575 | ("nsmid", "\x2224"),
1576 | ("nspar", "\x2226"),
1577 | ("nsqsube", "\x22e2"),
1578 | ("nsqsupe", "\x22e3"),
1579 | ("nsub", "\x2284"),
1580 | ("nsubE", "\x2ac5\x0338"),
1581 | ("nsube", "\x2288"),
1582 | ("nsubset", "\x2282\x20d2"),
1583 | ("nsubseteq", "\x2288"),
1584 | ("nsubseteqq", "\x2ac5\x0338"),
1585 | ("nsucc", "\x2281"),
1586 | ("nsucceq", "\x2ab0\x0338"),
1587 | ("nsup", "\x2285"),
1588 | ("nsupE", "\x2ac6\x0338"),
1589 | ("nsupe", "\x2289"),
1590 | ("nsupset", "\x2283\x20d2"),
1591 | ("nsupseteq", "\x2289"),
1592 | ("nsupseteqq", "\x2ac6\x0338"),
1593 | ("ntgl", "\x2279"),
1594 | ("ntild", "\x00f1"),
1595 | ("ntilde", "\x00f1"),
1596 | ("ntlg", "\x2278"),
1597 | ("ntriangleleft", "\x22ea"),
1598 | ("ntrianglelefteq", "\x22ec"),
1599 | ("ntriangleright", "\x22eb"),
1600 | ("ntrianglerighteq", "\x22ed"),
1601 | ("nu", "\x03bd"),
1602 | ("num", "\x0023"),
1603 | ("numero", "\x2116"),
1604 | ("numsp", "\x2007"),
1605 | ("nvDash", "\x22ad"),
1606 | ("nvHarr", "\x2904"),
1607 | ("nvap", "\x224d\x20d2"),
1608 | ("nvdash", "\x22ac"),
1609 | ("nvge", "\x2265\x20d2"),
1610 | ("nvgt", "\x003e\x20d2"),
1611 | ("nvinfin", "\x29de"),
1612 | ("nvlArr", "\x2902"),
1613 | ("nvle", "\x2264\x20d2"),
1614 | ("nvlt", "\x003c\x20d2"),
1615 | ("nvltrie", "\x22b4\x20d2"),
1616 | ("nvrArr", "\x2903"),
1617 | ("nvrtrie", "\x22b5\x20d2"),
1618 | ("nvsim", "\x223c\x20d2"),
1619 | ("nwArr", "\x21d6"),
1620 | ("nwarhk", "\x2923"),
1621 | ("nwarr", "\x2196"),
1622 | ("nwarrow", "\x2196"),
1623 | ("nwnear", "\x2927"),
1624 | ("oS", "\x24c8"),
1625 | ("oacut", "\x00f3"),
1626 | ("oacute", "\x00f3"),
1627 | ("oast", "\x229b"),
1628 | ("ocir", "\x229a"),
1629 | ("ocir", "\x00f4"),
1630 | ("ocirc", "\x00f4"),
1631 | ("ocy", "\x043e"),
1632 | ("odash", "\x229d"),
1633 | ("odblac", "\x0151"),
1634 | ("odiv", "\x2a38"),
1635 | ("odot", "\x2299"),
1636 | ("odsold", "\x29bc"),
1637 | ("oelig", "\x0153"),
1638 | ("ofcir", "\x29bf"),
1639 | ("ofr", "\x1d52c"),
1640 | ("ogon", "\x02db"),
1641 | ("ograv", "\x00f2"),
1642 | ("ograve", "\x00f2"),
1643 | ("ogt", "\x29c1"),
1644 | ("ohbar", "\x29b5"),
1645 | ("ohm", "\x03a9"),
1646 | ("oint", "\x222e"),
1647 | ("olarr", "\x21ba"),
1648 | ("olcir", "\x29be"),
1649 | ("olcross", "\x29bb"),
1650 | ("oline", "\x203e"),
1651 | ("olt", "\x29c0"),
1652 | ("omacr", "\x014d"),
1653 | ("omega", "\x03c9"),
1654 | ("omicron", "\x03bf"),
1655 | ("omid", "\x29b6"),
1656 | ("ominus", "\x2296"),
1657 | ("oopf", "\x1d560"),
1658 | ("opar", "\x29b7"),
1659 | ("operp", "\x29b9"),
1660 | ("oplus", "\x2295"),
1661 | ("or", "\x2228"),
1662 | ("orarr", "\x21bb"),
1663 | ("ord", "\x2a5d"),
1664 | ("order", "\x2134"),
1665 | ("orderof", "\x2134"),
1666 | ("ord", "\x00aa"),
1667 | ("ordf", "\x00aa"),
1668 | ("ord", "\x00ba"),
1669 | ("ordm", "\x00ba"),
1670 | ("origof", "\x22b6"),
1671 | ("oror", "\x2a56"),
1672 | ("orslope", "\x2a57"),
1673 | ("orv", "\x2a5b"),
1674 | ("oscr", "\x2134"),
1675 | ("oslas", "\x00f8"),
1676 | ("oslash", "\x00f8"),
1677 | ("osol", "\x2298"),
1678 | ("otild", "\x00f5"),
1679 | ("otilde", "\x00f5"),
1680 | ("otimes", "\x2297"),
1681 | ("otimesas", "\x2a36"),
1682 | ("oum", "\x00f6"),
1683 | ("ouml", "\x00f6"),
1684 | ("ovbar", "\x233d"),
1685 | ("par", "\x2225"),
1686 | ("par", "\x00b6"),
1687 | ("para", "\x00b6"),
1688 | ("parallel", "\x2225"),
1689 | ("parsim", "\x2af3"),
1690 | ("parsl", "\x2afd"),
1691 | ("part", "\x2202"),
1692 | ("pcy", "\x043f"),
1693 | ("percnt", "\x0025"),
1694 | ("period", "\x002e"),
1695 | ("permil", "\x2030"),
1696 | ("perp", "\x22a5"),
1697 | ("pertenk", "\x2031"),
1698 | ("pfr", "\x1d52d"),
1699 | ("phi", "\x03c6"),
1700 | ("phiv", "\x03d5"),
1701 | ("phmmat", "\x2133"),
1702 | ("phone", "\x260e"),
1703 | ("pi", "\x03c0"),
1704 | ("pitchfork", "\x22d4"),
1705 | ("piv", "\x03d6"),
1706 | ("planck", "\x210f"),
1707 | ("planckh", "\x210e"),
1708 | ("plankv", "\x210f"),
1709 | ("plus", "\x002b"),
1710 | ("plusacir", "\x2a23"),
1711 | ("plusb", "\x229e"),
1712 | ("pluscir", "\x2a22"),
1713 | ("plusdo", "\x2214"),
1714 | ("plusdu", "\x2a25"),
1715 | ("pluse", "\x2a72"),
1716 | ("plusm", "\x00b1"),
1717 | ("plusmn", "\x00b1"),
1718 | ("plussim", "\x2a26"),
1719 | ("plustwo", "\x2a27"),
1720 | ("pm", "\x00b1"),
1721 | ("pointint", "\x2a15"),
1722 | ("popf", "\x1d561"),
1723 | ("poun", "\x00a3"),
1724 | ("pound", "\x00a3"),
1725 | ("pr", "\x227a"),
1726 | ("prE", "\x2ab3"),
1727 | ("prap", "\x2ab7"),
1728 | ("prcue", "\x227c"),
1729 | ("pre", "\x2aaf"),
1730 | ("prec", "\x227a"),
1731 | ("precapprox", "\x2ab7"),
1732 | ("preccurlyeq", "\x227c"),
1733 | ("preceq", "\x2aaf"),
1734 | ("precnapprox", "\x2ab9"),
1735 | ("precneqq", "\x2ab5"),
1736 | ("precnsim", "\x22e8"),
1737 | ("precsim", "\x227e"),
1738 | ("prime", "\x2032"),
1739 | ("primes", "\x2119"),
1740 | ("prnE", "\x2ab5"),
1741 | ("prnap", "\x2ab9"),
1742 | ("prnsim", "\x22e8"),
1743 | ("prod", "\x220f"),
1744 | ("profalar", "\x232e"),
1745 | ("profline", "\x2312"),
1746 | ("profsurf", "\x2313"),
1747 | ("prop", "\x221d"),
1748 | ("propto", "\x221d"),
1749 | ("prsim", "\x227e"),
1750 | ("prurel", "\x22b0"),
1751 | ("pscr", "\x1d4c5"),
1752 | ("psi", "\x03c8"),
1753 | ("puncsp", "\x2008"),
1754 | ("qfr", "\x1d52e"),
1755 | ("qint", "\x2a0c"),
1756 | ("qopf", "\x1d562"),
1757 | ("qprime", "\x2057"),
1758 | ("qscr", "\x1d4c6"),
1759 | ("quaternions", "\x210d"),
1760 | ("quatint", "\x2a16"),
1761 | ("quest", "\x003f"),
1762 | ("questeq", "\x225f"),
1763 | ("quo", "\x0022"),
1764 | ("quot", "\x0022"),
1765 | ("rAarr", "\x21db"),
1766 | ("rArr", "\x21d2"),
1767 | ("rAtail", "\x291c"),
1768 | ("rBarr", "\x290f"),
1769 | ("rHar", "\x2964"),
1770 | ("race", "\x223d\x0331"),
1771 | ("racute", "\x0155"),
1772 | ("radic", "\x221a"),
1773 | ("raemptyv", "\x29b3"),
1774 | ("rang", "\x27e9"),
1775 | ("rangd", "\x2992"),
1776 | ("range", "\x29a5"),
1777 | ("rangle", "\x27e9"),
1778 | ("raqu", "\x00bb"),
1779 | ("raquo", "\x00bb"),
1780 | ("rarr", "\x2192"),
1781 | ("rarrap", "\x2975"),
1782 | ("rarrb", "\x21e5"),
1783 | ("rarrbfs", "\x2920"),
1784 | ("rarrc", "\x2933"),
1785 | ("rarrfs", "\x291e"),
1786 | ("rarrhk", "\x21aa"),
1787 | ("rarrlp", "\x21ac"),
1788 | ("rarrpl", "\x2945"),
1789 | ("rarrsim", "\x2974"),
1790 | ("rarrtl", "\x21a3"),
1791 | ("rarrw", "\x219d"),
1792 | ("ratail", "\x291a"),
1793 | ("ratio", "\x2236"),
1794 | ("rationals", "\x211a"),
1795 | ("rbarr", "\x290d"),
1796 | ("rbbrk", "\x2773"),
1797 | ("rbrace", "\x007d"),
1798 | ("rbrack", "\x005d"),
1799 | ("rbrke", "\x298c"),
1800 | ("rbrksld", "\x298e"),
1801 | ("rbrkslu", "\x2990"),
1802 | ("rcaron", "\x0159"),
1803 | ("rcedil", "\x0157"),
1804 | ("rceil", "\x2309"),
1805 | ("rcub", "\x007d"),
1806 | ("rcy", "\x0440"),
1807 | ("rdca", "\x2937"),
1808 | ("rdldhar", "\x2969"),
1809 | ("rdquo", "\x201d"),
1810 | ("rdquor", "\x201d"),
1811 | ("rdsh", "\x21b3"),
1812 | ("real", "\x211c"),
1813 | ("realine", "\x211b"),
1814 | ("realpart", "\x211c"),
1815 | ("reals", "\x211d"),
1816 | ("rect", "\x25ad"),
1817 | ("re", "\x00ae"),
1818 | ("reg", "\x00ae"),
1819 | ("rfisht", "\x297d"),
1820 | ("rfloor", "\x230b"),
1821 | ("rfr", "\x1d52f"),
1822 | ("rhard", "\x21c1"),
1823 | ("rharu", "\x21c0"),
1824 | ("rharul", "\x296c"),
1825 | ("rho", "\x03c1"),
1826 | ("rhov", "\x03f1"),
1827 | ("rightarrow", "\x2192"),
1828 | ("rightarrowtail", "\x21a3"),
1829 | ("rightharpoondown", "\x21c1"),
1830 | ("rightharpoonup", "\x21c0"),
1831 | ("rightleftarrows", "\x21c4"),
1832 | ("rightleftharpoons", "\x21cc"),
1833 | ("rightrightarrows", "\x21c9"),
1834 | ("rightsquigarrow", "\x219d"),
1835 | ("rightthreetimes", "\x22cc"),
1836 | ("ring", "\x02da"),
1837 | ("risingdotseq", "\x2253"),
1838 | ("rlarr", "\x21c4"),
1839 | ("rlhar", "\x21cc"),
1840 | ("rlm", "\x200f"),
1841 | ("rmoust", "\x23b1"),
1842 | ("rmoustache", "\x23b1"),
1843 | ("rnmid", "\x2aee"),
1844 | ("roang", "\x27ed"),
1845 | ("roarr", "\x21fe"),
1846 | ("robrk", "\x27e7"),
1847 | ("ropar", "\x2986"),
1848 | ("ropf", "\x1d563"),
1849 | ("roplus", "\x2a2e"),
1850 | ("rotimes", "\x2a35"),
1851 | ("rpar", "\x0029"),
1852 | ("rpargt", "\x2994"),
1853 | ("rppolint", "\x2a12"),
1854 | ("rrarr", "\x21c9"),
1855 | ("rsaquo", "\x203a"),
1856 | ("rscr", "\x1d4c7"),
1857 | ("rsh", "\x21b1"),
1858 | ("rsqb", "\x005d"),
1859 | ("rsquo", "\x2019"),
1860 | ("rsquor", "\x2019"),
1861 | ("rthree", "\x22cc"),
1862 | ("rtimes", "\x22ca"),
1863 | ("rtri", "\x25b9"),
1864 | ("rtrie", "\x22b5"),
1865 | ("rtrif", "\x25b8"),
1866 | ("rtriltri", "\x29ce"),
1867 | ("ruluhar", "\x2968"),
1868 | ("rx", "\x211e"),
1869 | ("sacute", "\x015b"),
1870 | ("sbquo", "\x201a"),
1871 | ("sc", "\x227b"),
1872 | ("scE", "\x2ab4"),
1873 | ("scap", "\x2ab8"),
1874 | ("scaron", "\x0161"),
1875 | ("sccue", "\x227d"),
1876 | ("sce", "\x2ab0"),
1877 | ("scedil", "\x015f"),
1878 | ("scirc", "\x015d"),
1879 | ("scnE", "\x2ab6"),
1880 | ("scnap", "\x2aba"),
1881 | ("scnsim", "\x22e9"),
1882 | ("scpolint", "\x2a13"),
1883 | ("scsim", "\x227f"),
1884 | ("scy", "\x0441"),
1885 | ("sdot", "\x22c5"),
1886 | ("sdotb", "\x22a1"),
1887 | ("sdote", "\x2a66"),
1888 | ("seArr", "\x21d8"),
1889 | ("searhk", "\x2925"),
1890 | ("searr", "\x2198"),
1891 | ("searrow", "\x2198"),
1892 | ("sec", "\x00a7"),
1893 | ("sect", "\x00a7"),
1894 | ("semi", "\x003b"),
1895 | ("seswar", "\x2929"),
1896 | ("setminus", "\x2216"),
1897 | ("setmn", "\x2216"),
1898 | ("sext", "\x2736"),
1899 | ("sfr", "\x1d530"),
1900 | ("sfrown", "\x2322"),
1901 | ("sharp", "\x266f"),
1902 | ("shchcy", "\x0449"),
1903 | ("shcy", "\x0448"),
1904 | ("shortmid", "\x2223"),
1905 | ("shortparallel", "\x2225"),
1906 | ("sh", "\x00ad"),
1907 | ("shy", "\x00ad"),
1908 | ("sigma", "\x03c3"),
1909 | ("sigmaf", "\x03c2"),
1910 | ("sigmav", "\x03c2"),
1911 | ("sim", "\x223c"),
1912 | ("simdot", "\x2a6a"),
1913 | ("sime", "\x2243"),
1914 | ("simeq", "\x2243"),
1915 | ("simg", "\x2a9e"),
1916 | ("simgE", "\x2aa0"),
1917 | ("siml", "\x2a9d"),
1918 | ("simlE", "\x2a9f"),
1919 | ("simne", "\x2246"),
1920 | ("simplus", "\x2a24"),
1921 | ("simrarr", "\x2972"),
1922 | ("slarr", "\x2190"),
1923 | ("smallsetminus", "\x2216"),
1924 | ("smashp", "\x2a33"),
1925 | ("smeparsl", "\x29e4"),
1926 | ("smid", "\x2223"),
1927 | ("smile", "\x2323"),
1928 | ("smt", "\x2aaa"),
1929 | ("smte", "\x2aac"),
1930 | ("smtes", "\x2aac\xfe00"),
1931 | ("softcy", "\x044c"),
1932 | ("sol", "\x002f"),
1933 | ("solb", "\x29c4"),
1934 | ("solbar", "\x233f"),
1935 | ("sopf", "\x1d564"),
1936 | ("spades", "\x2660"),
1937 | ("spadesuit", "\x2660"),
1938 | ("spar", "\x2225"),
1939 | ("sqcap", "\x2293"),
1940 | ("sqcaps", "\x2293\xfe00"),
1941 | ("sqcup", "\x2294"),
1942 | ("sqcups", "\x2294\xfe00"),
1943 | ("sqsub", "\x228f"),
1944 | ("sqsube", "\x2291"),
1945 | ("sqsubset", "\x228f"),
1946 | ("sqsubseteq", "\x2291"),
1947 | ("sqsup", "\x2290"),
1948 | ("sqsupe", "\x2292"),
1949 | ("sqsupset", "\x2290"),
1950 | ("sqsupseteq", "\x2292"),
1951 | ("squ", "\x25a1"),
1952 | ("square", "\x25a1"),
1953 | ("squarf", "\x25aa"),
1954 | ("squf", "\x25aa"),
1955 | ("srarr", "\x2192"),
1956 | ("sscr", "\x1d4c8"),
1957 | ("ssetmn", "\x2216"),
1958 | ("ssmile", "\x2323"),
1959 | ("sstarf", "\x22c6"),
1960 | ("star", "\x2606"),
1961 | ("starf", "\x2605"),
1962 | ("straightepsilon", "\x03f5"),
1963 | ("straightphi", "\x03d5"),
1964 | ("strns", "\x00af"),
1965 | ("sub", "\x2282"),
1966 | ("subE", "\x2ac5"),
1967 | ("subdot", "\x2abd"),
1968 | ("sube", "\x2286"),
1969 | ("subedot", "\x2ac3"),
1970 | ("submult", "\x2ac1"),
1971 | ("subnE", "\x2acb"),
1972 | ("subne", "\x228a"),
1973 | ("subplus", "\x2abf"),
1974 | ("subrarr", "\x2979"),
1975 | ("subset", "\x2282"),
1976 | ("subseteq", "\x2286"),
1977 | ("subseteqq", "\x2ac5"),
1978 | ("subsetneq", "\x228a"),
1979 | ("subsetneqq", "\x2acb"),
1980 | ("subsim", "\x2ac7"),
1981 | ("subsub", "\x2ad5"),
1982 | ("subsup", "\x2ad3"),
1983 | ("succ", "\x227b"),
1984 | ("succapprox", "\x2ab8"),
1985 | ("succcurlyeq", "\x227d"),
1986 | ("succeq", "\x2ab0"),
1987 | ("succnapprox", "\x2aba"),
1988 | ("succneqq", "\x2ab6"),
1989 | ("succnsim", "\x22e9"),
1990 | ("succsim", "\x227f"),
1991 | ("sum", "\x2211"),
1992 | ("sung", "\x266a"),
1993 | ("sup", "\x00b9"),
1994 | ("sup1", "\x00b9"),
1995 | ("sup", "\x00b2"),
1996 | ("sup2", "\x00b2"),
1997 | ("sup", "\x00b3"),
1998 | ("sup3", "\x00b3"),
1999 | ("sup", "\x2283"),
2000 | ("supE", "\x2ac6"),
2001 | ("supdot", "\x2abe"),
2002 | ("supdsub", "\x2ad8"),
2003 | ("supe", "\x2287"),
2004 | ("supedot", "\x2ac4"),
2005 | ("suphsol", "\x27c9"),
2006 | ("suphsub", "\x2ad7"),
2007 | ("suplarr", "\x297b"),
2008 | ("supmult", "\x2ac2"),
2009 | ("supnE", "\x2acc"),
2010 | ("supne", "\x228b"),
2011 | ("supplus", "\x2ac0"),
2012 | ("supset", "\x2283"),
2013 | ("supseteq", "\x2287"),
2014 | ("supseteqq", "\x2ac6"),
2015 | ("supsetneq", "\x228b"),
2016 | ("supsetneqq", "\x2acc"),
2017 | ("supsim", "\x2ac8"),
2018 | ("supsub", "\x2ad4"),
2019 | ("supsup", "\x2ad6"),
2020 | ("swArr", "\x21d9"),
2021 | ("swarhk", "\x2926"),
2022 | ("swarr", "\x2199"),
2023 | ("swarrow", "\x2199"),
2024 | ("swnwar", "\x292a"),
2025 | ("szli", "\x00df"),
2026 | ("szlig", "\x00df"),
2027 | ("target", "\x2316"),
2028 | ("tau", "\x03c4"),
2029 | ("tbrk", "\x23b4"),
2030 | ("tcaron", "\x0165"),
2031 | ("tcedil", "\x0163"),
2032 | ("tcy", "\x0442"),
2033 | ("tdot", "\x20db"),
2034 | ("telrec", "\x2315"),
2035 | ("tfr", "\x1d531"),
2036 | ("there4", "\x2234"),
2037 | ("therefore", "\x2234"),
2038 | ("theta", "\x03b8"),
2039 | ("thetasym", "\x03d1"),
2040 | ("thetav", "\x03d1"),
2041 | ("thickapprox", "\x2248"),
2042 | ("thicksim", "\x223c"),
2043 | ("thinsp", "\x2009"),
2044 | ("thkap", "\x2248"),
2045 | ("thksim", "\x223c"),
2046 | ("thor", "\x00fe"),
2047 | ("thorn", "\x00fe"),
2048 | ("tilde", "\x02dc"),
2049 | ("time", "\x00d7"),
2050 | ("times", "\x00d7"),
2051 | ("timesb", "\x22a0"),
2052 | ("timesbar", "\x2a31"),
2053 | ("timesd", "\x2a30"),
2054 | ("tint", "\x222d"),
2055 | ("toea", "\x2928"),
2056 | ("top", "\x22a4"),
2057 | ("topbot", "\x2336"),
2058 | ("topcir", "\x2af1"),
2059 | ("topf", "\x1d565"),
2060 | ("topfork", "\x2ada"),
2061 | ("tosa", "\x2929"),
2062 | ("tprime", "\x2034"),
2063 | ("trade", "\x2122"),
2064 | ("triangle", "\x25b5"),
2065 | ("triangledown", "\x25bf"),
2066 | ("triangleleft", "\x25c3"),
2067 | ("trianglelefteq", "\x22b4"),
2068 | ("triangleq", "\x225c"),
2069 | ("triangleright", "\x25b9"),
2070 | ("trianglerighteq", "\x22b5"),
2071 | ("tridot", "\x25ec"),
2072 | ("trie", "\x225c"),
2073 | ("triminus", "\x2a3a"),
2074 | ("triplus", "\x2a39"),
2075 | ("trisb", "\x29cd"),
2076 | ("tritime", "\x2a3b"),
2077 | ("trpezium", "\x23e2"),
2078 | ("tscr", "\x1d4c9"),
2079 | ("tscy", "\x0446"),
2080 | ("tshcy", "\x045b"),
2081 | ("tstrok", "\x0167"),
2082 | ("twixt", "\x226c"),
2083 | ("twoheadleftarrow", "\x219e"),
2084 | ("twoheadrightarrow", "\x21a0"),
2085 | ("uArr", "\x21d1"),
2086 | ("uHar", "\x2963"),
2087 | ("uacut", "\x00fa"),
2088 | ("uacute", "\x00fa"),
2089 | ("uarr", "\x2191"),
2090 | ("ubrcy", "\x045e"),
2091 | ("ubreve", "\x016d"),
2092 | ("ucir", "\x00fb"),
2093 | ("ucirc", "\x00fb"),
2094 | ("ucy", "\x0443"),
2095 | ("udarr", "\x21c5"),
2096 | ("udblac", "\x0171"),
2097 | ("udhar", "\x296e"),
2098 | ("ufisht", "\x297e"),
2099 | ("ufr", "\x1d532"),
2100 | ("ugrav", "\x00f9"),
2101 | ("ugrave", "\x00f9"),
2102 | ("uharl", "\x21bf"),
2103 | ("uharr", "\x21be"),
2104 | ("uhblk", "\x2580"),
2105 | ("ulcorn", "\x231c"),
2106 | ("ulcorner", "\x231c"),
2107 | ("ulcrop", "\x230f"),
2108 | ("ultri", "\x25f8"),
2109 | ("umacr", "\x016b"),
2110 | ("um", "\x00a8"),
2111 | ("uml", "\x00a8"),
2112 | ("uogon", "\x0173"),
2113 | ("uopf", "\x1d566"),
2114 | ("uparrow", "\x2191"),
2115 | ("updownarrow", "\x2195"),
2116 | ("upharpoonleft", "\x21bf"),
2117 | ("upharpoonright", "\x21be"),
2118 | ("uplus", "\x228e"),
2119 | ("upsi", "\x03c5"),
2120 | ("upsih", "\x03d2"),
2121 | ("upsilon", "\x03c5"),
2122 | ("upuparrows", "\x21c8"),
2123 | ("urcorn", "\x231d"),
2124 | ("urcorner", "\x231d"),
2125 | ("urcrop", "\x230e"),
2126 | ("uring", "\x016f"),
2127 | ("urtri", "\x25f9"),
2128 | ("uscr", "\x1d4ca"),
2129 | ("utdot", "\x22f0"),
2130 | ("utilde", "\x0169"),
2131 | ("utri", "\x25b5"),
2132 | ("utrif", "\x25b4"),
2133 | ("uuarr", "\x21c8"),
2134 | ("uum", "\x00fc"),
2135 | ("uuml", "\x00fc"),
2136 | ("uwangle", "\x29a7"),
2137 | ("vArr", "\x21d5"),
2138 | ("vBar", "\x2ae8"),
2139 | ("vBarv", "\x2ae9"),
2140 | ("vDash", "\x22a8"),
2141 | ("vangrt", "\x299c"),
2142 | ("varepsilon", "\x03f5"),
2143 | ("varkappa", "\x03f0"),
2144 | ("varnothing", "\x2205"),
2145 | ("varphi", "\x03d5"),
2146 | ("varpi", "\x03d6"),
2147 | ("varpropto", "\x221d"),
2148 | ("varr", "\x2195"),
2149 | ("varrho", "\x03f1"),
2150 | ("varsigma", "\x03c2"),
2151 | ("varsubsetneq", "\x228a\xfe00"),
2152 | ("varsubsetneqq", "\x2acb\xfe00"),
2153 | ("varsupsetneq", "\x228b\xfe00"),
2154 | ("varsupsetneqq", "\x2acc\xfe00"),
2155 | ("vartheta", "\x03d1"),
2156 | ("vartriangleleft", "\x22b2"),
2157 | ("vartriangleright", "\x22b3"),
2158 | ("vcy", "\x0432"),
2159 | ("vdash", "\x22a2"),
2160 | ("vee", "\x2228"),
2161 | ("veebar", "\x22bb"),
2162 | ("veeeq", "\x225a"),
2163 | ("vellip", "\x22ee"),
2164 | ("verbar", "\x007c"),
2165 | ("vert", "\x007c"),
2166 | ("vfr", "\x1d533"),
2167 | ("vltri", "\x22b2"),
2168 | ("vnsub", "\x2282\x20d2"),
2169 | ("vnsup", "\x2283\x20d2"),
2170 | ("vopf", "\x1d567"),
2171 | ("vprop", "\x221d"),
2172 | ("vrtri", "\x22b3"),
2173 | ("vscr", "\x1d4cb"),
2174 | ("vsubnE", "\x2acb\xfe00"),
2175 | ("vsubne", "\x228a\xfe00"),
2176 | ("vsupnE", "\x2acc\xfe00"),
2177 | ("vsupne", "\x228b\xfe00"),
2178 | ("vzigzag", "\x299a"),
2179 | ("wcirc", "\x0175"),
2180 | ("wedbar", "\x2a5f"),
2181 | ("wedge", "\x2227"),
2182 | ("wedgeq", "\x2259"),
2183 | ("weierp", "\x2118"),
2184 | ("wfr", "\x1d534"),
2185 | ("wopf", "\x1d568"),
2186 | ("wp", "\x2118"),
2187 | ("wr", "\x2240"),
2188 | ("wreath", "\x2240"),
2189 | ("wscr", "\x1d4cc"),
2190 | ("xcap", "\x22c2"),
2191 | ("xcirc", "\x25ef"),
2192 | ("xcup", "\x22c3"),
2193 | ("xdtri", "\x25bd"),
2194 | ("xfr", "\x1d535"),
2195 | ("xhArr", "\x27fa"),
2196 | ("xharr", "\x27f7"),
2197 | ("xi", "\x03be"),
2198 | ("xlArr", "\x27f8"),
2199 | ("xlarr", "\x27f5"),
2200 | ("xmap", "\x27fc"),
2201 | ("xnis", "\x22fb"),
2202 | ("xodot", "\x2a00"),
2203 | ("xopf", "\x1d569"),
2204 | ("xoplus", "\x2a01"),
2205 | ("xotime", "\x2a02"),
2206 | ("xrArr", "\x27f9"),
2207 | ("xrarr", "\x27f6"),
2208 | ("xscr", "\x1d4cd"),
2209 | ("xsqcup", "\x2a06"),
2210 | ("xuplus", "\x2a04"),
2211 | ("xutri", "\x25b3"),
2212 | ("xvee", "\x22c1"),
2213 | ("xwedge", "\x22c0"),
2214 | ("yacut", "\x00fd"),
2215 | ("yacute", "\x00fd"),
2216 | ("yacy", "\x044f"),
2217 | ("ycirc", "\x0177"),
2218 | ("ycy", "\x044b"),
2219 | ("ye", "\x00a5"),
2220 | ("yen", "\x00a5"),
2221 | ("yfr", "\x1d536"),
2222 | ("yicy", "\x0457"),
2223 | ("yopf", "\x1d56a"),
2224 | ("yscr", "\x1d4ce"),
2225 | ("yucy", "\x044e"),
2226 | ("yum", "\x00ff"),
2227 | ("yuml", "\x00ff"),
2228 | ("zacute", "\x017a"),
2229 | ("zcaron", "\x017e"),
2230 | ("zcy", "\x0437"),
2231 | ("zdot", "\x017c"),
2232 | ("zeetrf", "\x2128"),
2233 | ("zeta", "\x03b6"),
2234 | ("zfr", "\x1d537"),
2235 | ("zhcy", "\x0436"),
2236 | ("zigrarr", "\x21dd"),
2237 | ("zopf", "\x1d56b"),
2238 | ("zscr", "\x1d4cf"),
2239 | ("zwj", "\x200d"),
2240 | ("zwnj", "\x200c")
2241 | ]
2242 |
--------------------------------------------------------------------------------